{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A type for representing D-Bus messages that can be sent or received
-- on a t'GI.Gio.Objects.DBusConnection.DBusConnection'.
-- 
-- /Since: 2.26/

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

module GI.Gio.Objects.DBusMessage
    ( 

-- * Exported types
    DBusMessage(..)                         ,
    IsDBusMessage                           ,
    toDBusMessage                           ,


 -- * 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"), [copy]("GI.Gio.Objects.DBusMessage#g:method:copy"), [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"), [lock]("GI.Gio.Objects.DBusMessage#g:method:lock"), [newMethodErrorLiteral]("GI.Gio.Objects.DBusMessage#g:method:newMethodErrorLiteral"), [newMethodReply]("GI.Gio.Objects.DBusMessage#g:method:newMethodReply"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [print]("GI.Gio.Objects.DBusMessage#g:method:print"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [toBlob]("GI.Gio.Objects.DBusMessage#g:method:toBlob"), [toGerror]("GI.Gio.Objects.DBusMessage#g:method:toGerror"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getArg0]("GI.Gio.Objects.DBusMessage#g:method:getArg0"), [getArg0Path]("GI.Gio.Objects.DBusMessage#g:method:getArg0Path"), [getBody]("GI.Gio.Objects.DBusMessage#g:method:getBody"), [getByteOrder]("GI.Gio.Objects.DBusMessage#g:method:getByteOrder"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDestination]("GI.Gio.Objects.DBusMessage#g:method:getDestination"), [getErrorName]("GI.Gio.Objects.DBusMessage#g:method:getErrorName"), [getFlags]("GI.Gio.Objects.DBusMessage#g:method:getFlags"), [getHeader]("GI.Gio.Objects.DBusMessage#g:method:getHeader"), [getHeaderFields]("GI.Gio.Objects.DBusMessage#g:method:getHeaderFields"), [getInterface]("GI.Gio.Objects.DBusMessage#g:method:getInterface"), [getLocked]("GI.Gio.Objects.DBusMessage#g:method:getLocked"), [getMember]("GI.Gio.Objects.DBusMessage#g:method:getMember"), [getMessageType]("GI.Gio.Objects.DBusMessage#g:method:getMessageType"), [getNumUnixFds]("GI.Gio.Objects.DBusMessage#g:method:getNumUnixFds"), [getPath]("GI.Gio.Objects.DBusMessage#g:method:getPath"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getReplySerial]("GI.Gio.Objects.DBusMessage#g:method:getReplySerial"), [getSender]("GI.Gio.Objects.DBusMessage#g:method:getSender"), [getSerial]("GI.Gio.Objects.DBusMessage#g:method:getSerial"), [getSignature]("GI.Gio.Objects.DBusMessage#g:method:getSignature"), [getUnixFdList]("GI.Gio.Objects.DBusMessage#g:method:getUnixFdList").
-- 
-- ==== Setters
-- [setBody]("GI.Gio.Objects.DBusMessage#g:method:setBody"), [setByteOrder]("GI.Gio.Objects.DBusMessage#g:method:setByteOrder"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDestination]("GI.Gio.Objects.DBusMessage#g:method:setDestination"), [setErrorName]("GI.Gio.Objects.DBusMessage#g:method:setErrorName"), [setFlags]("GI.Gio.Objects.DBusMessage#g:method:setFlags"), [setHeader]("GI.Gio.Objects.DBusMessage#g:method:setHeader"), [setInterface]("GI.Gio.Objects.DBusMessage#g:method:setInterface"), [setMember]("GI.Gio.Objects.DBusMessage#g:method:setMember"), [setMessageType]("GI.Gio.Objects.DBusMessage#g:method:setMessageType"), [setNumUnixFds]("GI.Gio.Objects.DBusMessage#g:method:setNumUnixFds"), [setPath]("GI.Gio.Objects.DBusMessage#g:method:setPath"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setReplySerial]("GI.Gio.Objects.DBusMessage#g:method:setReplySerial"), [setSender]("GI.Gio.Objects.DBusMessage#g:method:setSender"), [setSerial]("GI.Gio.Objects.DBusMessage#g:method:setSerial"), [setSignature]("GI.Gio.Objects.DBusMessage#g:method:setSignature"), [setUnixFdList]("GI.Gio.Objects.DBusMessage#g:method:setUnixFdList").

#if defined(ENABLE_OVERLOADING)
    ResolveDBusMessageMethod                ,
#endif

-- ** bytesNeeded #method:bytesNeeded#

    dBusMessageBytesNeeded                  ,


-- ** copy #method:copy#

#if defined(ENABLE_OVERLOADING)
    DBusMessageCopyMethodInfo               ,
#endif
    dBusMessageCopy                         ,


-- ** getArg0 #method:getArg0#

#if defined(ENABLE_OVERLOADING)
    DBusMessageGetArg0MethodInfo            ,
#endif
    dBusMessageGetArg0                      ,


-- ** getArg0Path #method:getArg0Path#

#if defined(ENABLE_OVERLOADING)
    DBusMessageGetArg0PathMethodInfo        ,
#endif
    dBusMessageGetArg0Path                  ,


-- ** getBody #method:getBody#

#if defined(ENABLE_OVERLOADING)
    DBusMessageGetBodyMethodInfo            ,
#endif
    dBusMessageGetBody                      ,


-- ** getByteOrder #method:getByteOrder#

#if defined(ENABLE_OVERLOADING)
    DBusMessageGetByteOrderMethodInfo       ,
#endif
    dBusMessageGetByteOrder                 ,


-- ** getDestination #method:getDestination#

#if defined(ENABLE_OVERLOADING)
    DBusMessageGetDestinationMethodInfo     ,
#endif
    dBusMessageGetDestination               ,


-- ** getErrorName #method:getErrorName#

#if defined(ENABLE_OVERLOADING)
    DBusMessageGetErrorNameMethodInfo       ,
#endif
    dBusMessageGetErrorName                 ,


-- ** getFlags #method:getFlags#

#if defined(ENABLE_OVERLOADING)
    DBusMessageGetFlagsMethodInfo           ,
#endif
    dBusMessageGetFlags                     ,


-- ** getHeader #method:getHeader#

#if defined(ENABLE_OVERLOADING)
    DBusMessageGetHeaderMethodInfo          ,
#endif
    dBusMessageGetHeader                    ,


-- ** getHeaderFields #method:getHeaderFields#

#if defined(ENABLE_OVERLOADING)
    DBusMessageGetHeaderFieldsMethodInfo    ,
#endif
    dBusMessageGetHeaderFields              ,


-- ** getInterface #method:getInterface#

#if defined(ENABLE_OVERLOADING)
    DBusMessageGetInterfaceMethodInfo       ,
#endif
    dBusMessageGetInterface                 ,


-- ** getLocked #method:getLocked#

#if defined(ENABLE_OVERLOADING)
    DBusMessageGetLockedMethodInfo          ,
#endif
    dBusMessageGetLocked                    ,


-- ** getMember #method:getMember#

#if defined(ENABLE_OVERLOADING)
    DBusMessageGetMemberMethodInfo          ,
#endif
    dBusMessageGetMember                    ,


-- ** getMessageType #method:getMessageType#

#if defined(ENABLE_OVERLOADING)
    DBusMessageGetMessageTypeMethodInfo     ,
#endif
    dBusMessageGetMessageType               ,


-- ** getNumUnixFds #method:getNumUnixFds#

#if defined(ENABLE_OVERLOADING)
    DBusMessageGetNumUnixFdsMethodInfo      ,
#endif
    dBusMessageGetNumUnixFds                ,


-- ** getPath #method:getPath#

#if defined(ENABLE_OVERLOADING)
    DBusMessageGetPathMethodInfo            ,
#endif
    dBusMessageGetPath                      ,


-- ** getReplySerial #method:getReplySerial#

#if defined(ENABLE_OVERLOADING)
    DBusMessageGetReplySerialMethodInfo     ,
#endif
    dBusMessageGetReplySerial               ,


-- ** getSender #method:getSender#

#if defined(ENABLE_OVERLOADING)
    DBusMessageGetSenderMethodInfo          ,
#endif
    dBusMessageGetSender                    ,


-- ** getSerial #method:getSerial#

#if defined(ENABLE_OVERLOADING)
    DBusMessageGetSerialMethodInfo          ,
#endif
    dBusMessageGetSerial                    ,


-- ** getSignature #method:getSignature#

#if defined(ENABLE_OVERLOADING)
    DBusMessageGetSignatureMethodInfo       ,
#endif
    dBusMessageGetSignature                 ,


-- ** getUnixFdList #method:getUnixFdList#

#if defined(ENABLE_OVERLOADING)
    DBusMessageGetUnixFdListMethodInfo      ,
#endif
    dBusMessageGetUnixFdList                ,


-- ** lock #method:lock#

#if defined(ENABLE_OVERLOADING)
    DBusMessageLockMethodInfo               ,
#endif
    dBusMessageLock                         ,


-- ** new #method:new#

    dBusMessageNew                          ,


-- ** newFromBlob #method:newFromBlob#

    dBusMessageNewFromBlob                  ,


-- ** newMethodCall #method:newMethodCall#

    dBusMessageNewMethodCall                ,


-- ** newMethodErrorLiteral #method:newMethodErrorLiteral#

#if defined(ENABLE_OVERLOADING)
    DBusMessageNewMethodErrorLiteralMethodInfo,
#endif
    dBusMessageNewMethodErrorLiteral        ,


-- ** newMethodReply #method:newMethodReply#

#if defined(ENABLE_OVERLOADING)
    DBusMessageNewMethodReplyMethodInfo     ,
#endif
    dBusMessageNewMethodReply               ,


-- ** newSignal #method:newSignal#

    dBusMessageNewSignal                    ,


-- ** print #method:print#

#if defined(ENABLE_OVERLOADING)
    DBusMessagePrintMethodInfo              ,
#endif
    dBusMessagePrint                        ,


-- ** setBody #method:setBody#

#if defined(ENABLE_OVERLOADING)
    DBusMessageSetBodyMethodInfo            ,
#endif
    dBusMessageSetBody                      ,


-- ** setByteOrder #method:setByteOrder#

#if defined(ENABLE_OVERLOADING)
    DBusMessageSetByteOrderMethodInfo       ,
#endif
    dBusMessageSetByteOrder                 ,


-- ** setDestination #method:setDestination#

#if defined(ENABLE_OVERLOADING)
    DBusMessageSetDestinationMethodInfo     ,
#endif
    dBusMessageSetDestination               ,


-- ** setErrorName #method:setErrorName#

#if defined(ENABLE_OVERLOADING)
    DBusMessageSetErrorNameMethodInfo       ,
#endif
    dBusMessageSetErrorName                 ,


-- ** setFlags #method:setFlags#

#if defined(ENABLE_OVERLOADING)
    DBusMessageSetFlagsMethodInfo           ,
#endif
    dBusMessageSetFlags                     ,


-- ** setHeader #method:setHeader#

#if defined(ENABLE_OVERLOADING)
    DBusMessageSetHeaderMethodInfo          ,
#endif
    dBusMessageSetHeader                    ,


-- ** setInterface #method:setInterface#

#if defined(ENABLE_OVERLOADING)
    DBusMessageSetInterfaceMethodInfo       ,
#endif
    dBusMessageSetInterface                 ,


-- ** setMember #method:setMember#

#if defined(ENABLE_OVERLOADING)
    DBusMessageSetMemberMethodInfo          ,
#endif
    dBusMessageSetMember                    ,


-- ** setMessageType #method:setMessageType#

#if defined(ENABLE_OVERLOADING)
    DBusMessageSetMessageTypeMethodInfo     ,
#endif
    dBusMessageSetMessageType               ,


-- ** setNumUnixFds #method:setNumUnixFds#

#if defined(ENABLE_OVERLOADING)
    DBusMessageSetNumUnixFdsMethodInfo      ,
#endif
    dBusMessageSetNumUnixFds                ,


-- ** setPath #method:setPath#

#if defined(ENABLE_OVERLOADING)
    DBusMessageSetPathMethodInfo            ,
#endif
    dBusMessageSetPath                      ,


-- ** setReplySerial #method:setReplySerial#

#if defined(ENABLE_OVERLOADING)
    DBusMessageSetReplySerialMethodInfo     ,
#endif
    dBusMessageSetReplySerial               ,


-- ** setSender #method:setSender#

#if defined(ENABLE_OVERLOADING)
    DBusMessageSetSenderMethodInfo          ,
#endif
    dBusMessageSetSender                    ,


-- ** setSerial #method:setSerial#

#if defined(ENABLE_OVERLOADING)
    DBusMessageSetSerialMethodInfo          ,
#endif
    dBusMessageSetSerial                    ,


-- ** setSignature #method:setSignature#

#if defined(ENABLE_OVERLOADING)
    DBusMessageSetSignatureMethodInfo       ,
#endif
    dBusMessageSetSignature                 ,


-- ** setUnixFdList #method:setUnixFdList#

#if defined(ENABLE_OVERLOADING)
    DBusMessageSetUnixFdListMethodInfo      ,
#endif
    dBusMessageSetUnixFdList                ,


-- ** toBlob #method:toBlob#

#if defined(ENABLE_OVERLOADING)
    DBusMessageToBlobMethodInfo             ,
#endif
    dBusMessageToBlob                       ,


-- ** toGerror #method:toGerror#

#if defined(ENABLE_OVERLOADING)
    DBusMessageToGerrorMethodInfo           ,
#endif
    dBusMessageToGerror                     ,




 -- * Properties


-- ** locked #attr:locked#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DBusMessageLockedPropertyInfo           ,
#endif
#if defined(ENABLE_OVERLOADING)
    dBusMessageLocked                       ,
#endif
    getDBusMessageLocked                    ,




    ) 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.Kind as DK
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 Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Enums as Gio.Enums
import {-# SOURCE #-} qualified GI.Gio.Flags as Gio.Flags
import {-# SOURCE #-} qualified GI.Gio.Objects.UnixFDList as Gio.UnixFDList

#else
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Enums as Gio.Enums
import {-# SOURCE #-} qualified GI.Gio.Flags as Gio.Flags
import {-# SOURCE #-} qualified GI.Gio.Objects.UnixFDList as Gio.UnixFDList

#endif

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

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

foreign import ccall "g_dbus_message_get_type"
    c_g_dbus_message_get_type :: IO B.Types.GType

instance B.Types.TypedObject DBusMessage where
    glibType :: IO GType
glibType = IO GType
c_g_dbus_message_get_type

instance B.Types.GObject DBusMessage

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveDBusMessageMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveDBusMessageMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDBusMessageMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDBusMessageMethod "copy" o = DBusMessageCopyMethodInfo
    ResolveDBusMessageMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDBusMessageMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDBusMessageMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDBusMessageMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDBusMessageMethod "lock" o = DBusMessageLockMethodInfo
    ResolveDBusMessageMethod "newMethodErrorLiteral" o = DBusMessageNewMethodErrorLiteralMethodInfo
    ResolveDBusMessageMethod "newMethodReply" o = DBusMessageNewMethodReplyMethodInfo
    ResolveDBusMessageMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDBusMessageMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDBusMessageMethod "print" o = DBusMessagePrintMethodInfo
    ResolveDBusMessageMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDBusMessageMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDBusMessageMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDBusMessageMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDBusMessageMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDBusMessageMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDBusMessageMethod "toBlob" o = DBusMessageToBlobMethodInfo
    ResolveDBusMessageMethod "toGerror" o = DBusMessageToGerrorMethodInfo
    ResolveDBusMessageMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDBusMessageMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDBusMessageMethod "getArg0" o = DBusMessageGetArg0MethodInfo
    ResolveDBusMessageMethod "getArg0Path" o = DBusMessageGetArg0PathMethodInfo
    ResolveDBusMessageMethod "getBody" o = DBusMessageGetBodyMethodInfo
    ResolveDBusMessageMethod "getByteOrder" o = DBusMessageGetByteOrderMethodInfo
    ResolveDBusMessageMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDBusMessageMethod "getDestination" o = DBusMessageGetDestinationMethodInfo
    ResolveDBusMessageMethod "getErrorName" o = DBusMessageGetErrorNameMethodInfo
    ResolveDBusMessageMethod "getFlags" o = DBusMessageGetFlagsMethodInfo
    ResolveDBusMessageMethod "getHeader" o = DBusMessageGetHeaderMethodInfo
    ResolveDBusMessageMethod "getHeaderFields" o = DBusMessageGetHeaderFieldsMethodInfo
    ResolveDBusMessageMethod "getInterface" o = DBusMessageGetInterfaceMethodInfo
    ResolveDBusMessageMethod "getLocked" o = DBusMessageGetLockedMethodInfo
    ResolveDBusMessageMethod "getMember" o = DBusMessageGetMemberMethodInfo
    ResolveDBusMessageMethod "getMessageType" o = DBusMessageGetMessageTypeMethodInfo
    ResolveDBusMessageMethod "getNumUnixFds" o = DBusMessageGetNumUnixFdsMethodInfo
    ResolveDBusMessageMethod "getPath" o = DBusMessageGetPathMethodInfo
    ResolveDBusMessageMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDBusMessageMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDBusMessageMethod "getReplySerial" o = DBusMessageGetReplySerialMethodInfo
    ResolveDBusMessageMethod "getSender" o = DBusMessageGetSenderMethodInfo
    ResolveDBusMessageMethod "getSerial" o = DBusMessageGetSerialMethodInfo
    ResolveDBusMessageMethod "getSignature" o = DBusMessageGetSignatureMethodInfo
    ResolveDBusMessageMethod "getUnixFdList" o = DBusMessageGetUnixFdListMethodInfo
    ResolveDBusMessageMethod "setBody" o = DBusMessageSetBodyMethodInfo
    ResolveDBusMessageMethod "setByteOrder" o = DBusMessageSetByteOrderMethodInfo
    ResolveDBusMessageMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDBusMessageMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDBusMessageMethod "setDestination" o = DBusMessageSetDestinationMethodInfo
    ResolveDBusMessageMethod "setErrorName" o = DBusMessageSetErrorNameMethodInfo
    ResolveDBusMessageMethod "setFlags" o = DBusMessageSetFlagsMethodInfo
    ResolveDBusMessageMethod "setHeader" o = DBusMessageSetHeaderMethodInfo
    ResolveDBusMessageMethod "setInterface" o = DBusMessageSetInterfaceMethodInfo
    ResolveDBusMessageMethod "setMember" o = DBusMessageSetMemberMethodInfo
    ResolveDBusMessageMethod "setMessageType" o = DBusMessageSetMessageTypeMethodInfo
    ResolveDBusMessageMethod "setNumUnixFds" o = DBusMessageSetNumUnixFdsMethodInfo
    ResolveDBusMessageMethod "setPath" o = DBusMessageSetPathMethodInfo
    ResolveDBusMessageMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDBusMessageMethod "setReplySerial" o = DBusMessageSetReplySerialMethodInfo
    ResolveDBusMessageMethod "setSender" o = DBusMessageSetSenderMethodInfo
    ResolveDBusMessageMethod "setSerial" o = DBusMessageSetSerialMethodInfo
    ResolveDBusMessageMethod "setSignature" o = DBusMessageSetSignatureMethodInfo
    ResolveDBusMessageMethod "setUnixFdList" o = DBusMessageSetUnixFdListMethodInfo
    ResolveDBusMessageMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- VVV Prop "locked"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@locked@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusMessage #locked
-- @
getDBusMessageLocked :: (MonadIO m, IsDBusMessage o) => o -> m Bool
getDBusMessageLocked :: forall (m :: * -> *) o. (MonadIO m, IsDBusMessage o) => o -> m Bool
getDBusMessageLocked o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"locked"

#if defined(ENABLE_OVERLOADING)
data DBusMessageLockedPropertyInfo
instance AttrInfo DBusMessageLockedPropertyInfo where
    type AttrAllowedOps DBusMessageLockedPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DBusMessageLockedPropertyInfo = IsDBusMessage
    type AttrSetTypeConstraint DBusMessageLockedPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DBusMessageLockedPropertyInfo = (~) ()
    type AttrTransferType DBusMessageLockedPropertyInfo = ()
    type AttrGetType DBusMessageLockedPropertyInfo = Bool
    type AttrLabel DBusMessageLockedPropertyInfo = "locked"
    type AttrOrigin DBusMessageLockedPropertyInfo = DBusMessage
    attrGet = getDBusMessageLocked
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.locked"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#g:attr:locked"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DBusMessage
type instance O.AttributeList DBusMessage = DBusMessageAttributeList
type DBusMessageAttributeList = ('[ '("locked", DBusMessageLockedPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
dBusMessageLocked :: AttrLabelProxy "locked"
dBusMessageLocked = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DBusMessage = DBusMessageSignalList
type DBusMessageSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method DBusMessage::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "DBusMessage" })
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_message_new" g_dbus_message_new :: 
    IO (Ptr DBusMessage)

-- | Creates a new empty t'GI.Gio.Objects.DBusMessage.DBusMessage'.
-- 
-- /Since: 2.26/
dBusMessageNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m DBusMessage
    -- ^ __Returns:__ A t'GI.Gio.Objects.DBusMessage.DBusMessage'. Free with 'GI.GObject.Objects.Object.objectUnref'.
dBusMessageNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m DBusMessage
dBusMessageNew  = IO DBusMessage -> m DBusMessage
forall a. IO a -> m a
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
    result <- IO (Ptr DBusMessage)
g_dbus_message_new
    checkUnexpectedReturnNULL "dBusMessageNew" result
    result' <- (wrapObject DBusMessage) result
    return result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method DBusMessage::new_from_blob
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "blob"
--           , argType = TCArray False (-1) 1 (TBasicType TUInt8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A blob representing a binary D-Bus message."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "blob_len"
--           , argType = TBasicType TSize
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of @blob."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "capabilities"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusCapabilityFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GDBusCapabilityFlags describing what protocol features are supported."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "blob_len"
--              , argType = TBasicType TSize
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "The length of @blob."
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , argCallbackUserData = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "DBusMessage" })
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_message_new_from_blob" g_dbus_message_new_from_blob :: 
    Ptr Word8 ->                            -- blob : TCArray False (-1) 1 (TBasicType TUInt8)
    FCT.CSize ->                            -- blob_len : TBasicType TSize
    CUInt ->                                -- capabilities : TInterface (Name {namespace = "Gio", name = "DBusCapabilityFlags"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr DBusMessage)

-- | Creates a new t'GI.Gio.Objects.DBusMessage.DBusMessage' from the data stored at /@blob@/. The byte
-- order that the message was in can be retrieved using
-- 'GI.Gio.Objects.DBusMessage.dBusMessageGetByteOrder'.
-- 
-- If the /@blob@/ cannot be parsed, contains invalid fields, or contains invalid
-- headers, 'GI.Gio.Enums.IOErrorEnumInvalidArgument' will be returned.
-- 
-- /Since: 2.26/
dBusMessageNewFromBlob ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteString
    -- ^ /@blob@/: A blob representing a binary D-Bus message.
    -> [Gio.Flags.DBusCapabilityFlags]
    -- ^ /@capabilities@/: A t'GI.Gio.Flags.DBusCapabilityFlags' describing what protocol features are supported.
    -> m DBusMessage
    -- ^ __Returns:__ A new t'GI.Gio.Objects.DBusMessage.DBusMessage' or 'P.Nothing' if /@error@/ is set. Free with
    -- 'GI.GObject.Objects.Object.objectUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
dBusMessageNewFromBlob :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ByteString -> [DBusCapabilityFlags] -> m DBusMessage
dBusMessageNewFromBlob ByteString
blob [DBusCapabilityFlags]
capabilities = IO DBusMessage -> m DBusMessage
forall a. IO a -> m a
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
    let blobLen :: CSize
blobLen = Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CSize) -> Int -> CSize
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
blob
    blob' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
blob
    let capabilities' = [DBusCapabilityFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusCapabilityFlags]
capabilities
    onException (do
        result <- propagateGError $ g_dbus_message_new_from_blob blob' blobLen capabilities'
        checkUnexpectedReturnNULL "dBusMessageNewFromBlob" result
        result' <- (wrapObject DBusMessage) result
        freeMem blob'
        return result'
     ) (do
        freeMem blob'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method DBusMessage::new_method_call
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A valid D-Bus name or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A valid object path."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interface_"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A valid D-Bus interface name or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "method"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A valid method name."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "DBusMessage" })
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_message_new_method_call" g_dbus_message_new_method_call :: 
    CString ->                              -- name : TBasicType TUTF8
    CString ->                              -- path : TBasicType TUTF8
    CString ->                              -- interface_ : TBasicType TUTF8
    CString ->                              -- method : TBasicType TUTF8
    IO (Ptr DBusMessage)

-- | Creates a new t'GI.Gio.Objects.DBusMessage.DBusMessage' for a method call.
-- 
-- /Since: 2.26/
dBusMessageNewMethodCall ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Maybe (T.Text)
    -- ^ /@name@/: A valid D-Bus name or 'P.Nothing'.
    -> T.Text
    -- ^ /@path@/: A valid object path.
    -> Maybe (T.Text)
    -- ^ /@interface_@/: A valid D-Bus interface name or 'P.Nothing'.
    -> T.Text
    -- ^ /@method@/: A valid method name.
    -> m DBusMessage
    -- ^ __Returns:__ A t'GI.Gio.Objects.DBusMessage.DBusMessage'. Free with 'GI.GObject.Objects.Object.objectUnref'.
dBusMessageNewMethodCall :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Maybe Text -> Text -> Maybe Text -> Text -> m DBusMessage
dBusMessageNewMethodCall Maybe Text
name Text
path Maybe Text
interface_ Text
method = IO DBusMessage -> m DBusMessage
forall a. IO a -> m a
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
    maybeName <- case Maybe Text
name of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
FP.nullPtr
        Just Text
jName -> do
            jName' <- Text -> IO (Ptr CChar)
textToCString Text
jName
            return jName'
    path' <- textToCString path
    maybeInterface_ <- case interface_ of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
FP.nullPtr
        Just Text
jInterface_ -> do
            jInterface_' <- Text -> IO (Ptr CChar)
textToCString Text
jInterface_
            return jInterface_'
    method' <- textToCString method
    result <- g_dbus_message_new_method_call maybeName path' maybeInterface_ method'
    checkUnexpectedReturnNULL "dBusMessageNewMethodCall" result
    result' <- (wrapObject DBusMessage) result
    freeMem maybeName
    freeMem path'
    freeMem maybeInterface_
    freeMem method'
    return result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method DBusMessage::new_signal
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A valid object path."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interface_"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A valid D-Bus interface name."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "signal"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A valid signal name."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "DBusMessage" })
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_message_new_signal" g_dbus_message_new_signal :: 
    CString ->                              -- path : TBasicType TUTF8
    CString ->                              -- interface_ : TBasicType TUTF8
    CString ->                              -- signal : TBasicType TUTF8
    IO (Ptr DBusMessage)

-- | Creates a new t'GI.Gio.Objects.DBusMessage.DBusMessage' for a signal emission.
-- 
-- /Since: 2.26/
dBusMessageNewSignal ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@path@/: A valid object path.
    -> T.Text
    -- ^ /@interface_@/: A valid D-Bus interface name.
    -> T.Text
    -- ^ /@signal@/: A valid signal name.
    -> m DBusMessage
    -- ^ __Returns:__ A t'GI.Gio.Objects.DBusMessage.DBusMessage'. Free with 'GI.GObject.Objects.Object.objectUnref'.
dBusMessageNewSignal :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> Text -> Text -> m DBusMessage
dBusMessageNewSignal Text
path Text
interface_ Text
signal = IO DBusMessage -> m DBusMessage
forall a. IO a -> m a
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
    path' <- Text -> IO (Ptr CChar)
textToCString Text
path
    interface_' <- textToCString interface_
    signal' <- textToCString signal
    result <- g_dbus_message_new_signal path' interface_' signal'
    checkUnexpectedReturnNULL "dBusMessageNewSignal" result
    result' <- (wrapObject DBusMessage) result
    freeMem path'
    freeMem interface_'
    freeMem signal'
    return result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "g_dbus_message_copy" g_dbus_message_copy :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr DBusMessage)

-- | Copies /@message@/. The copy is a deep copy and the returned
-- t'GI.Gio.Objects.DBusMessage.DBusMessage' is completely identical except that it is guaranteed
-- to not be locked.
-- 
-- This operation can fail if e.g. /@message@/ contains file descriptors
-- and the per-process or system-wide open files limit is reached.
-- 
-- /Since: 2.26/
dBusMessageCopy ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> m DBusMessage
    -- ^ __Returns:__ A new t'GI.Gio.Objects.DBusMessage.DBusMessage' or 'P.Nothing' if /@error@/ is set.
    --     Free with 'GI.GObject.Objects.Object.objectUnref'. /(Can throw 'Data.GI.Base.GError.GError')/
dBusMessageCopy :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> m DBusMessage
dBusMessageCopy a
message = IO DBusMessage -> m DBusMessage
forall a. IO a -> m a
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
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    onException (do
        result <- propagateGError $ g_dbus_message_copy message'
        checkUnexpectedReturnNULL "dBusMessageCopy" result
        result' <- (wrapObject DBusMessage) result
        touchManagedPtr message
        return result'
     ) (do
        return ()
     )

#if defined(ENABLE_OVERLOADING)
data DBusMessageCopyMethodInfo
instance (signature ~ (m DBusMessage), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageCopyMethodInfo a signature where
    overloadedMethod = dBusMessageCopy

instance O.OverloadedMethodInfo DBusMessageCopyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageCopy",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageCopy"
        })


#endif

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

foreign import ccall "g_dbus_message_get_arg0" g_dbus_message_get_arg0 :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    IO CString

-- | Convenience to get the first item in the body of /@message@/.
-- 
-- See 'GI.Gio.Objects.DBusMessage.dBusMessageGetArg0Path' for returning object-path-typed
-- arg0 values.
-- 
-- /Since: 2.26/
dBusMessageGetArg0 ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> m (Maybe T.Text)
    -- ^ __Returns:__ The string item or 'P.Nothing' if the first item in the body of
    -- /@message@/ is not a string.
dBusMessageGetArg0 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> m (Maybe Text)
dBusMessageGetArg0 a
message = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    result <- g_dbus_message_get_arg0 message'
    maybeResult <- convertIfNonNull result $ \Ptr CChar
result' -> do
        result'' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result'
        return result''
    touchManagedPtr message
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetArg0MethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageGetArg0MethodInfo a signature where
    overloadedMethod = dBusMessageGetArg0

instance O.OverloadedMethodInfo DBusMessageGetArg0MethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageGetArg0",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageGetArg0"
        })


#endif

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

foreign import ccall "g_dbus_message_get_arg0_path" g_dbus_message_get_arg0_path :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    IO CString

-- | Convenience to get the first item in the body of /@message@/.
-- 
-- See 'GI.Gio.Objects.DBusMessage.dBusMessageGetArg0' for returning string-typed arg0 values.
-- 
-- /Since: 2.80/
dBusMessageGetArg0Path ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A @GDBusMessage@.
    -> m (Maybe T.Text)
    -- ^ __Returns:__ The object path item or @NULL@ if the first item in the
    --   body of /@message@/ is not an object path.
dBusMessageGetArg0Path :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> m (Maybe Text)
dBusMessageGetArg0Path a
message = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    result <- g_dbus_message_get_arg0_path message'
    maybeResult <- convertIfNonNull result $ \Ptr CChar
result' -> do
        result'' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result'
        return result''
    touchManagedPtr message
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetArg0PathMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageGetArg0PathMethodInfo a signature where
    overloadedMethod = dBusMessageGetArg0Path

instance O.OverloadedMethodInfo DBusMessageGetArg0PathMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageGetArg0Path",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageGetArg0Path"
        })


#endif

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

foreign import ccall "g_dbus_message_get_body" g_dbus_message_get_body :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    IO (Ptr GVariant)

-- | Gets the body of a message.
-- 
-- /Since: 2.26/
dBusMessageGetBody ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> m (Maybe GVariant)
    -- ^ __Returns:__ A t'GVariant' or 'P.Nothing' if the body is
    -- empty. Do not free, it is owned by /@message@/.
dBusMessageGetBody :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> m (Maybe GVariant)
dBusMessageGetBody a
message = IO (Maybe GVariant) -> m (Maybe GVariant)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe GVariant) -> m (Maybe GVariant))
-> IO (Maybe GVariant) -> m (Maybe GVariant)
forall a b. (a -> b) -> a -> b
$ do
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    result <- g_dbus_message_get_body message'
    maybeResult <- convertIfNonNull result $ \Ptr GVariant
result' -> do
        result'' <- Ptr GVariant -> IO GVariant
B.GVariant.newGVariantFromPtr Ptr GVariant
result'
        return result''
    touchManagedPtr message
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetBodyMethodInfo
instance (signature ~ (m (Maybe GVariant)), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageGetBodyMethodInfo a signature where
    overloadedMethod = dBusMessageGetBody

instance O.OverloadedMethodInfo DBusMessageGetBodyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageGetBody",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageGetBody"
        })


#endif

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

foreign import ccall "g_dbus_message_get_byte_order" g_dbus_message_get_byte_order :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    IO CUInt

-- | Gets the byte order of /@message@/.
dBusMessageGetByteOrder ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> m Gio.Enums.DBusMessageByteOrder
    -- ^ __Returns:__ The byte order.
dBusMessageGetByteOrder :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> m DBusMessageByteOrder
dBusMessageGetByteOrder a
message = IO DBusMessageByteOrder -> m DBusMessageByteOrder
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusMessageByteOrder -> m DBusMessageByteOrder)
-> IO DBusMessageByteOrder -> m DBusMessageByteOrder
forall a b. (a -> b) -> a -> b
$ do
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    result <- g_dbus_message_get_byte_order message'
    let result' = (Int -> DBusMessageByteOrder
forall a. Enum a => Int -> a
toEnum (Int -> DBusMessageByteOrder)
-> (CUInt -> Int) -> CUInt -> DBusMessageByteOrder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    touchManagedPtr message
    return result'

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetByteOrderMethodInfo
instance (signature ~ (m Gio.Enums.DBusMessageByteOrder), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageGetByteOrderMethodInfo a signature where
    overloadedMethod = dBusMessageGetByteOrder

instance O.OverloadedMethodInfo DBusMessageGetByteOrderMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageGetByteOrder",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageGetByteOrder"
        })


#endif

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

foreign import ccall "g_dbus_message_get_destination" g_dbus_message_get_destination :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    IO CString

-- | Convenience getter for the 'GI.Gio.Enums.DBusMessageHeaderFieldDestination' header field.
-- 
-- /Since: 2.26/
dBusMessageGetDestination ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> m (Maybe T.Text)
    -- ^ __Returns:__ The value.
dBusMessageGetDestination :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> m (Maybe Text)
dBusMessageGetDestination a
message = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    result <- g_dbus_message_get_destination message'
    maybeResult <- convertIfNonNull result $ \Ptr CChar
result' -> do
        result'' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result'
        return result''
    touchManagedPtr message
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetDestinationMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageGetDestinationMethodInfo a signature where
    overloadedMethod = dBusMessageGetDestination

instance O.OverloadedMethodInfo DBusMessageGetDestinationMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageGetDestination",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageGetDestination"
        })


#endif

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

foreign import ccall "g_dbus_message_get_error_name" g_dbus_message_get_error_name :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    IO CString

-- | Convenience getter for the 'GI.Gio.Enums.DBusMessageHeaderFieldErrorName' header field.
-- 
-- /Since: 2.26/
dBusMessageGetErrorName ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> m (Maybe T.Text)
    -- ^ __Returns:__ The value.
dBusMessageGetErrorName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> m (Maybe Text)
dBusMessageGetErrorName a
message = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    result <- g_dbus_message_get_error_name message'
    maybeResult <- convertIfNonNull result $ \Ptr CChar
result' -> do
        result'' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result'
        return result''
    touchManagedPtr message
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetErrorNameMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageGetErrorNameMethodInfo a signature where
    overloadedMethod = dBusMessageGetErrorName

instance O.OverloadedMethodInfo DBusMessageGetErrorNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageGetErrorName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageGetErrorName"
        })


#endif

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

foreign import ccall "g_dbus_message_get_flags" g_dbus_message_get_flags :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    IO CUInt

-- | Gets the flags for /@message@/.
-- 
-- /Since: 2.26/
dBusMessageGetFlags ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> m [Gio.Flags.DBusMessageFlags]
    -- ^ __Returns:__ Flags that are set (typically values from the t'GI.Gio.Flags.DBusMessageFlags' enumeration bitwise ORed together).
dBusMessageGetFlags :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> m [DBusMessageFlags]
dBusMessageGetFlags a
message = IO [DBusMessageFlags] -> m [DBusMessageFlags]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [DBusMessageFlags] -> m [DBusMessageFlags])
-> IO [DBusMessageFlags] -> m [DBusMessageFlags]
forall a b. (a -> b) -> a -> b
$ do
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    result <- g_dbus_message_get_flags message'
    let result' = CUInt -> [DBusMessageFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    touchManagedPtr message
    return result'

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetFlagsMethodInfo
instance (signature ~ (m [Gio.Flags.DBusMessageFlags]), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageGetFlagsMethodInfo a signature where
    overloadedMethod = dBusMessageGetFlags

instance O.OverloadedMethodInfo DBusMessageGetFlagsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageGetFlags",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageGetFlags"
        })


#endif

-- method DBusMessage::get_header
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "message"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMessage." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "header_field"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusMessageHeaderField" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A 8-bit unsigned integer (typically a value from the #GDBusMessageHeaderField enumeration)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just TVariant
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_message_get_header" g_dbus_message_get_header :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    CUInt ->                                -- header_field : TInterface (Name {namespace = "Gio", name = "DBusMessageHeaderField"})
    IO (Ptr GVariant)

-- | Gets a header field on /@message@/.
-- 
-- The caller is responsible for checking the type of the returned t'GVariant'
-- matches what is expected.
-- 
-- /Since: 2.26/
dBusMessageGetHeader ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> Gio.Enums.DBusMessageHeaderField
    -- ^ /@headerField@/: A 8-bit unsigned integer (typically a value from the t'GI.Gio.Enums.DBusMessageHeaderField' enumeration)
    -> m (Maybe GVariant)
    -- ^ __Returns:__ A t'GVariant' with the value if the header was found, 'P.Nothing'
    -- otherwise. Do not free, it is owned by /@message@/.
dBusMessageGetHeader :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> DBusMessageHeaderField -> m (Maybe GVariant)
dBusMessageGetHeader a
message DBusMessageHeaderField
headerField = IO (Maybe GVariant) -> m (Maybe GVariant)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe GVariant) -> m (Maybe GVariant))
-> IO (Maybe GVariant) -> m (Maybe GVariant)
forall a b. (a -> b) -> a -> b
$ do
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    let headerField' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (DBusMessageHeaderField -> Int)
-> DBusMessageHeaderField
-> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DBusMessageHeaderField -> Int
forall a. Enum a => a -> Int
fromEnum) DBusMessageHeaderField
headerField
    result <- g_dbus_message_get_header message' headerField'
    maybeResult <- convertIfNonNull result $ \Ptr GVariant
result' -> do
        result'' <- Ptr GVariant -> IO GVariant
B.GVariant.newGVariantFromPtr Ptr GVariant
result'
        return result''
    touchManagedPtr message
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetHeaderMethodInfo
instance (signature ~ (Gio.Enums.DBusMessageHeaderField -> m (Maybe GVariant)), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageGetHeaderMethodInfo a signature where
    overloadedMethod = dBusMessageGetHeader

instance O.OverloadedMethodInfo DBusMessageGetHeaderMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageGetHeader",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageGetHeader"
        })


#endif

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

foreign import ccall "g_dbus_message_get_header_fields" g_dbus_message_get_header_fields :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    IO (Ptr Word8)

-- | Gets an array of all header fields on /@message@/ that are set.
-- 
-- /Since: 2.26/
dBusMessageGetHeaderFields ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> m ByteString
    -- ^ __Returns:__ An array of header fields
    -- terminated by 'GI.Gio.Enums.DBusMessageHeaderFieldInvalid'.  Each element
    -- is a @/guchar/@. Free with 'GI.GLib.Functions.free'.
dBusMessageGetHeaderFields :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> m ByteString
dBusMessageGetHeaderFields a
message = IO ByteString -> m ByteString
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteString -> m ByteString) -> IO ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ do
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    result <- g_dbus_message_get_header_fields message'
    checkUnexpectedReturnNULL "dBusMessageGetHeaderFields" result
    result' <- unpackZeroTerminatedByteString result
    touchManagedPtr message
    return result'

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetHeaderFieldsMethodInfo
instance (signature ~ (m ByteString), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageGetHeaderFieldsMethodInfo a signature where
    overloadedMethod = dBusMessageGetHeaderFields

instance O.OverloadedMethodInfo DBusMessageGetHeaderFieldsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageGetHeaderFields",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageGetHeaderFields"
        })


#endif

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

foreign import ccall "g_dbus_message_get_interface" g_dbus_message_get_interface :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    IO CString

-- | Convenience getter for the 'GI.Gio.Enums.DBusMessageHeaderFieldInterface' header field.
-- 
-- /Since: 2.26/
dBusMessageGetInterface ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> m (Maybe T.Text)
    -- ^ __Returns:__ The value.
dBusMessageGetInterface :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> m (Maybe Text)
dBusMessageGetInterface a
message = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    result <- g_dbus_message_get_interface message'
    maybeResult <- convertIfNonNull result $ \Ptr CChar
result' -> do
        result'' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result'
        return result''
    touchManagedPtr message
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetInterfaceMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageGetInterfaceMethodInfo a signature where
    overloadedMethod = dBusMessageGetInterface

instance O.OverloadedMethodInfo DBusMessageGetInterfaceMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageGetInterface",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageGetInterface"
        })


#endif

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

foreign import ccall "g_dbus_message_get_locked" g_dbus_message_get_locked :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    IO CInt

-- | Checks whether /@message@/ is locked. To monitor changes to this
-- value, conncet to the [Object::notify]("GI.GObject.Objects.Object#g:signal:notify") signal to listen for changes
-- on the [DBusMessage:locked]("GI.Gio.Objects.DBusMessage#g:attr:locked") property.
-- 
-- /Since: 2.26/
dBusMessageGetLocked ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@message@/ is locked, 'P.False' otherwise.
dBusMessageGetLocked :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> m Bool
dBusMessageGetLocked a
message = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    result <- g_dbus_message_get_locked message'
    let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    touchManagedPtr message
    return result'

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetLockedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageGetLockedMethodInfo a signature where
    overloadedMethod = dBusMessageGetLocked

instance O.OverloadedMethodInfo DBusMessageGetLockedMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageGetLocked",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageGetLocked"
        })


#endif

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

foreign import ccall "g_dbus_message_get_member" g_dbus_message_get_member :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    IO CString

-- | Convenience getter for the 'GI.Gio.Enums.DBusMessageHeaderFieldMember' header field.
-- 
-- /Since: 2.26/
dBusMessageGetMember ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> m (Maybe T.Text)
    -- ^ __Returns:__ The value.
dBusMessageGetMember :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> m (Maybe Text)
dBusMessageGetMember a
message = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    result <- g_dbus_message_get_member message'
    maybeResult <- convertIfNonNull result $ \Ptr CChar
result' -> do
        result'' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result'
        return result''
    touchManagedPtr message
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetMemberMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageGetMemberMethodInfo a signature where
    overloadedMethod = dBusMessageGetMember

instance O.OverloadedMethodInfo DBusMessageGetMemberMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageGetMember",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageGetMember"
        })


#endif

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

foreign import ccall "g_dbus_message_get_message_type" g_dbus_message_get_message_type :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    IO CUInt

-- | Gets the type of /@message@/.
-- 
-- /Since: 2.26/
dBusMessageGetMessageType ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> m Gio.Enums.DBusMessageType
    -- ^ __Returns:__ A 8-bit unsigned integer (typically a value from the t'GI.Gio.Enums.DBusMessageType' enumeration).
dBusMessageGetMessageType :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> m DBusMessageType
dBusMessageGetMessageType a
message = IO DBusMessageType -> m DBusMessageType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusMessageType -> m DBusMessageType)
-> IO DBusMessageType -> m DBusMessageType
forall a b. (a -> b) -> a -> b
$ do
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    result <- g_dbus_message_get_message_type message'
    let result' = (Int -> DBusMessageType
forall a. Enum a => Int -> a
toEnum (Int -> DBusMessageType)
-> (CUInt -> Int) -> CUInt -> DBusMessageType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    touchManagedPtr message
    return result'

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetMessageTypeMethodInfo
instance (signature ~ (m Gio.Enums.DBusMessageType), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageGetMessageTypeMethodInfo a signature where
    overloadedMethod = dBusMessageGetMessageType

instance O.OverloadedMethodInfo DBusMessageGetMessageTypeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageGetMessageType",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageGetMessageType"
        })


#endif

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

foreign import ccall "g_dbus_message_get_num_unix_fds" g_dbus_message_get_num_unix_fds :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    IO Word32

-- | Convenience getter for the 'GI.Gio.Enums.DBusMessageHeaderFieldNumUnixFds' header field.
-- 
-- /Since: 2.26/
dBusMessageGetNumUnixFds ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> m Word32
    -- ^ __Returns:__ The value.
dBusMessageGetNumUnixFds :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> m Word32
dBusMessageGetNumUnixFds a
message = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    result <- g_dbus_message_get_num_unix_fds message'
    touchManagedPtr message
    return result

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetNumUnixFdsMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageGetNumUnixFdsMethodInfo a signature where
    overloadedMethod = dBusMessageGetNumUnixFds

instance O.OverloadedMethodInfo DBusMessageGetNumUnixFdsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageGetNumUnixFds",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageGetNumUnixFds"
        })


#endif

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

foreign import ccall "g_dbus_message_get_path" g_dbus_message_get_path :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    IO CString

-- | Convenience getter for the 'GI.Gio.Enums.DBusMessageHeaderFieldPath' header field.
-- 
-- /Since: 2.26/
dBusMessageGetPath ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> m (Maybe T.Text)
    -- ^ __Returns:__ The value.
dBusMessageGetPath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> m (Maybe Text)
dBusMessageGetPath a
message = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    result <- g_dbus_message_get_path message'
    maybeResult <- convertIfNonNull result $ \Ptr CChar
result' -> do
        result'' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result'
        return result''
    touchManagedPtr message
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetPathMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageGetPathMethodInfo a signature where
    overloadedMethod = dBusMessageGetPath

instance O.OverloadedMethodInfo DBusMessageGetPathMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageGetPath",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageGetPath"
        })


#endif

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

foreign import ccall "g_dbus_message_get_reply_serial" g_dbus_message_get_reply_serial :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    IO Word32

-- | Convenience getter for the 'GI.Gio.Enums.DBusMessageHeaderFieldReplySerial' header field.
-- 
-- /Since: 2.26/
dBusMessageGetReplySerial ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> m Word32
    -- ^ __Returns:__ The value.
dBusMessageGetReplySerial :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> m Word32
dBusMessageGetReplySerial a
message = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    result <- g_dbus_message_get_reply_serial message'
    touchManagedPtr message
    return result

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetReplySerialMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageGetReplySerialMethodInfo a signature where
    overloadedMethod = dBusMessageGetReplySerial

instance O.OverloadedMethodInfo DBusMessageGetReplySerialMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageGetReplySerial",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageGetReplySerial"
        })


#endif

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

foreign import ccall "g_dbus_message_get_sender" g_dbus_message_get_sender :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    IO CString

-- | Convenience getter for the 'GI.Gio.Enums.DBusMessageHeaderFieldSender' header field.
-- 
-- /Since: 2.26/
dBusMessageGetSender ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> m (Maybe T.Text)
    -- ^ __Returns:__ The value.
dBusMessageGetSender :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> m (Maybe Text)
dBusMessageGetSender a
message = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    result <- g_dbus_message_get_sender message'
    maybeResult <- convertIfNonNull result $ \Ptr CChar
result' -> do
        result'' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result'
        return result''
    touchManagedPtr message
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetSenderMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageGetSenderMethodInfo a signature where
    overloadedMethod = dBusMessageGetSender

instance O.OverloadedMethodInfo DBusMessageGetSenderMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageGetSender",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageGetSender"
        })


#endif

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

foreign import ccall "g_dbus_message_get_serial" g_dbus_message_get_serial :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    IO Word32

-- | Gets the serial for /@message@/.
-- 
-- /Since: 2.26/
dBusMessageGetSerial ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> m Word32
    -- ^ __Returns:__ A @/guint32/@.
dBusMessageGetSerial :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> m Word32
dBusMessageGetSerial a
message = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    result <- g_dbus_message_get_serial message'
    touchManagedPtr message
    return result

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetSerialMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageGetSerialMethodInfo a signature where
    overloadedMethod = dBusMessageGetSerial

instance O.OverloadedMethodInfo DBusMessageGetSerialMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageGetSerial",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageGetSerial"
        })


#endif

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

foreign import ccall "g_dbus_message_get_signature" g_dbus_message_get_signature :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    IO CString

-- | Convenience getter for the 'GI.Gio.Enums.DBusMessageHeaderFieldSignature' header field.
-- 
-- This will always be non-'P.Nothing', but may be an empty string.
-- 
-- /Since: 2.26/
dBusMessageGetSignature ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> m T.Text
    -- ^ __Returns:__ The value.
dBusMessageGetSignature :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> m Text
dBusMessageGetSignature a
message = 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
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    result <- g_dbus_message_get_signature message'
    checkUnexpectedReturnNULL "dBusMessageGetSignature" result
    result' <- cstringToText result
    touchManagedPtr message
    return result'

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetSignatureMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageGetSignatureMethodInfo a signature where
    overloadedMethod = dBusMessageGetSignature

instance O.OverloadedMethodInfo DBusMessageGetSignatureMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageGetSignature",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageGetSignature"
        })


#endif

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

foreign import ccall "g_dbus_message_get_unix_fd_list" g_dbus_message_get_unix_fd_list :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    IO (Ptr Gio.UnixFDList.UnixFDList)

-- | Gets the UNIX file descriptors associated with /@message@/, if any.
-- 
-- This method is only available on UNIX.
-- 
-- The file descriptors normally correspond to @/G_VARIANT_TYPE_HANDLE/@
-- values in the body of the message. For example,
-- if 'GI.GLib.Structs.Variant.variantGetHandle' returns 5, that is intended to be a reference
-- to the file descriptor that can be accessed by
-- @g_unix_fd_list_get (list, 5, ...)@.
-- 
-- /Since: 2.26/
dBusMessageGetUnixFdList ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> m (Maybe Gio.UnixFDList.UnixFDList)
    -- ^ __Returns:__ A t'GI.Gio.Objects.UnixFDList.UnixFDList' or 'P.Nothing' if no file descriptors are
    -- associated. Do not free, this object is owned by /@message@/.
dBusMessageGetUnixFdList :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> m (Maybe UnixFDList)
dBusMessageGetUnixFdList a
message = IO (Maybe UnixFDList) -> m (Maybe UnixFDList)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe UnixFDList) -> m (Maybe UnixFDList))
-> IO (Maybe UnixFDList) -> m (Maybe UnixFDList)
forall a b. (a -> b) -> a -> b
$ do
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    result <- g_dbus_message_get_unix_fd_list message'
    maybeResult <- convertIfNonNull result $ \Ptr UnixFDList
result' -> do
        result'' <- ((ManagedPtr UnixFDList -> UnixFDList)
-> Ptr UnixFDList -> IO UnixFDList
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr UnixFDList -> UnixFDList
Gio.UnixFDList.UnixFDList) Ptr UnixFDList
result'
        return result''
    touchManagedPtr message
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetUnixFdListMethodInfo
instance (signature ~ (m (Maybe Gio.UnixFDList.UnixFDList)), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageGetUnixFdListMethodInfo a signature where
    overloadedMethod = dBusMessageGetUnixFdList

instance O.OverloadedMethodInfo DBusMessageGetUnixFdListMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageGetUnixFdList",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageGetUnixFdList"
        })


#endif

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

foreign import ccall "g_dbus_message_lock" g_dbus_message_lock :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    IO ()

-- | If /@message@/ is locked, does nothing. Otherwise locks the message.
-- 
-- /Since: 2.26/
dBusMessageLock ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> m ()
dBusMessageLock :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> m ()
dBusMessageLock a
message = 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
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    g_dbus_message_lock message'
    touchManagedPtr message
    return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageLockMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageLockMethodInfo a signature where
    overloadedMethod = dBusMessageLock

instance O.OverloadedMethodInfo DBusMessageLockMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageLock",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageLock"
        })


#endif

-- method DBusMessage::new_method_error_literal
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "method_call_message"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A message of type %G_DBUS_MESSAGE_TYPE_METHOD_CALL to\ncreate a reply message to."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "error_message"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The D-Bus error message."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "DBusMessage" })
-- throws : False
-- Skip return : False

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

-- | Creates a new t'GI.Gio.Objects.DBusMessage.DBusMessage' that is an error reply to /@methodCallMessage@/.
-- 
-- /Since: 2.26/
dBusMessageNewMethodErrorLiteral ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@methodCallMessage@/: A message of type 'GI.Gio.Enums.DBusMessageTypeMethodCall' to
    -- create a reply message to.
    -> T.Text
    -- ^ /@errorName@/: A valid D-Bus error name.
    -> T.Text
    -- ^ /@errorMessage@/: The D-Bus error message.
    -> m DBusMessage
    -- ^ __Returns:__ A t'GI.Gio.Objects.DBusMessage.DBusMessage'. Free with 'GI.GObject.Objects.Object.objectUnref'.
dBusMessageNewMethodErrorLiteral :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> Text -> Text -> m DBusMessage
dBusMessageNewMethodErrorLiteral a
methodCallMessage Text
errorName Text
errorMessage = IO DBusMessage -> m DBusMessage
forall a. IO a -> m a
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
    methodCallMessage' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
methodCallMessage
    errorName' <- textToCString errorName
    errorMessage' <- textToCString errorMessage
    result <- g_dbus_message_new_method_error_literal methodCallMessage' errorName' errorMessage'
    checkUnexpectedReturnNULL "dBusMessageNewMethodErrorLiteral" result
    result' <- (wrapObject DBusMessage) result
    touchManagedPtr methodCallMessage
    freeMem errorName'
    freeMem errorMessage'
    return result'

#if defined(ENABLE_OVERLOADING)
data DBusMessageNewMethodErrorLiteralMethodInfo
instance (signature ~ (T.Text -> T.Text -> m DBusMessage), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageNewMethodErrorLiteralMethodInfo a signature where
    overloadedMethod = dBusMessageNewMethodErrorLiteral

instance O.OverloadedMethodInfo DBusMessageNewMethodErrorLiteralMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageNewMethodErrorLiteral",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageNewMethodErrorLiteral"
        })


#endif

-- method DBusMessage::new_method_reply
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "method_call_message"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A message of type %G_DBUS_MESSAGE_TYPE_METHOD_CALL to\ncreate a reply message to."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "DBusMessage" })
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_message_new_method_reply" g_dbus_message_new_method_reply :: 
    Ptr DBusMessage ->                      -- method_call_message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    IO (Ptr DBusMessage)

-- | Creates a new t'GI.Gio.Objects.DBusMessage.DBusMessage' that is a reply to /@methodCallMessage@/.
-- 
-- /Since: 2.26/
dBusMessageNewMethodReply ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@methodCallMessage@/: A message of type 'GI.Gio.Enums.DBusMessageTypeMethodCall' to
    -- create a reply message to.
    -> m DBusMessage
    -- ^ __Returns:__ t'GI.Gio.Objects.DBusMessage.DBusMessage'. Free with 'GI.GObject.Objects.Object.objectUnref'.
dBusMessageNewMethodReply :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> m DBusMessage
dBusMessageNewMethodReply a
methodCallMessage = IO DBusMessage -> m DBusMessage
forall a. IO a -> m a
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
    methodCallMessage' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
methodCallMessage
    result <- g_dbus_message_new_method_reply methodCallMessage'
    checkUnexpectedReturnNULL "dBusMessageNewMethodReply" result
    result' <- (wrapObject DBusMessage) result
    touchManagedPtr methodCallMessage
    return result'

#if defined(ENABLE_OVERLOADING)
data DBusMessageNewMethodReplyMethodInfo
instance (signature ~ (m DBusMessage), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageNewMethodReplyMethodInfo a signature where
    overloadedMethod = dBusMessageNewMethodReply

instance O.OverloadedMethodInfo DBusMessageNewMethodReplyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageNewMethodReply",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageNewMethodReply"
        })


#endif

-- method DBusMessage::print
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "message"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMessage." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "indent"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Indentation level." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_message_print" g_dbus_message_print :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    Word32 ->                               -- indent : TBasicType TUInt
    IO CString

-- | Produces a human-readable multi-line description of /@message@/.
-- 
-- The contents of the description has no ABI guarantees, the contents
-- and formatting is subject to change at any time. Typical output
-- looks something like this:
-- >Flags:   none
-- >Version: 0
-- >Serial:  4
-- >Headers:
-- >  path -> objectpath '/org/gtk/GDBus/TestObject'
-- >  interface -> 'org.gtk.GDBus.TestInterface'
-- >  member -> 'GimmeStdout'
-- >  destination -> ':1.146'
-- >Body: ()
-- >UNIX File Descriptors:
-- >  (none)
-- 
-- or
-- >Flags:   no-reply-expected
-- >Version: 0
-- >Serial:  477
-- >Headers:
-- >  reply-serial -> uint32 4
-- >  destination -> ':1.159'
-- >  sender -> ':1.146'
-- >  num-unix-fds -> uint32 1
-- >Body: ()
-- >UNIX File Descriptors:
-- >  fd 12: dev=0:10,mode=020620,ino=5,uid=500,gid=5,rdev=136:2,size=0,atime=1273085037,mtime=1273085851,ctime=1272982635
-- 
-- 
-- /Since: 2.26/
dBusMessagePrint ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> Word32
    -- ^ /@indent@/: Indentation level.
    -> m T.Text
    -- ^ __Returns:__ A string that should be freed with 'GI.GLib.Functions.free'.
dBusMessagePrint :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> Word32 -> m Text
dBusMessagePrint a
message Word32
indent = 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
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    result <- g_dbus_message_print message' indent
    checkUnexpectedReturnNULL "dBusMessagePrint" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr message
    return result'

#if defined(ENABLE_OVERLOADING)
data DBusMessagePrintMethodInfo
instance (signature ~ (Word32 -> m T.Text), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessagePrintMethodInfo a signature where
    overloadedMethod = dBusMessagePrint

instance O.OverloadedMethodInfo DBusMessagePrintMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessagePrint",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessagePrint"
        })


#endif

-- method DBusMessage::set_body
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "message"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMessage." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "body"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Either %NULL or a #GVariant that is a tuple."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_message_set_body" g_dbus_message_set_body :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    Ptr GVariant ->                         -- body : TVariant
    IO ()

-- | Sets the body /@message@/. As a side-effect the
-- 'GI.Gio.Enums.DBusMessageHeaderFieldSignature' header field is set to the
-- type string of /@body@/ (or cleared if /@body@/ is 'P.Nothing').
-- 
-- If /@body@/ is floating, /@message@/ assumes ownership of /@body@/.
-- 
-- /Since: 2.26/
dBusMessageSetBody ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> GVariant
    -- ^ /@body@/: Either 'P.Nothing' or a t'GVariant' that is a tuple.
    -> m ()
dBusMessageSetBody :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> GVariant -> m ()
dBusMessageSetBody a
message GVariant
body = 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
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    body' <- unsafeManagedPtrGetPtr body
    g_dbus_message_set_body message' body'
    touchManagedPtr message
    touchManagedPtr body
    return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetBodyMethodInfo
instance (signature ~ (GVariant -> m ()), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageSetBodyMethodInfo a signature where
    overloadedMethod = dBusMessageSetBody

instance O.OverloadedMethodInfo DBusMessageSetBodyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageSetBody",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageSetBody"
        })


#endif

-- method DBusMessage::set_byte_order
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "message"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMessage." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "byte_order"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusMessageByteOrder" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The byte order." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_message_set_byte_order" g_dbus_message_set_byte_order :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    CUInt ->                                -- byte_order : TInterface (Name {namespace = "Gio", name = "DBusMessageByteOrder"})
    IO ()

-- | Sets the byte order of /@message@/.
dBusMessageSetByteOrder ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> Gio.Enums.DBusMessageByteOrder
    -- ^ /@byteOrder@/: The byte order.
    -> m ()
dBusMessageSetByteOrder :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> DBusMessageByteOrder -> m ()
dBusMessageSetByteOrder a
message DBusMessageByteOrder
byteOrder = 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
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    let byteOrder' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (DBusMessageByteOrder -> Int) -> DBusMessageByteOrder -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DBusMessageByteOrder -> Int
forall a. Enum a => a -> Int
fromEnum) DBusMessageByteOrder
byteOrder
    g_dbus_message_set_byte_order message' byteOrder'
    touchManagedPtr message
    return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetByteOrderMethodInfo
instance (signature ~ (Gio.Enums.DBusMessageByteOrder -> m ()), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageSetByteOrderMethodInfo a signature where
    overloadedMethod = dBusMessageSetByteOrder

instance O.OverloadedMethodInfo DBusMessageSetByteOrderMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageSetByteOrder",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageSetByteOrder"
        })


#endif

-- method DBusMessage::set_destination
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "message"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMessage." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The value to set." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_message_set_destination" g_dbus_message_set_destination :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    CString ->                              -- value : TBasicType TUTF8
    IO ()

-- | Convenience setter for the 'GI.Gio.Enums.DBusMessageHeaderFieldDestination' header field.
-- 
-- /Since: 2.26/
dBusMessageSetDestination ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> Maybe (T.Text)
    -- ^ /@value@/: The value to set.
    -> m ()
dBusMessageSetDestination :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> Maybe Text -> m ()
dBusMessageSetDestination a
message Maybe Text
value = 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
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    maybeValue <- case value of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
FP.nullPtr
        Just Text
jValue -> do
            jValue' <- Text -> IO (Ptr CChar)
textToCString Text
jValue
            return jValue'
    g_dbus_message_set_destination message' maybeValue
    touchManagedPtr message
    freeMem maybeValue
    return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetDestinationMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageSetDestinationMethodInfo a signature where
    overloadedMethod = dBusMessageSetDestination

instance O.OverloadedMethodInfo DBusMessageSetDestinationMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageSetDestination",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageSetDestination"
        })


#endif

-- method DBusMessage::set_error_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "message"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessage" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMessage." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The value to set." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_message_set_error_name" g_dbus_message_set_error_name :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    CString ->                              -- value : TBasicType TUTF8
    IO ()

-- | Convenience setter for the 'GI.Gio.Enums.DBusMessageHeaderFieldErrorName' header field.
-- 
-- /Since: 2.26/
dBusMessageSetErrorName ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    Maybe (a)
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> T.Text
    -- ^ /@value@/: The value to set.
    -> m ()
dBusMessageSetErrorName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
Maybe a -> Text -> m ()
dBusMessageSetErrorName Maybe a
message Text
value = 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
    maybeMessage <- case Maybe a
message of
        Maybe a
Nothing -> Ptr DBusMessage -> IO (Ptr DBusMessage)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DBusMessage
forall a. Ptr a
FP.nullPtr
        Just a
jMessage -> do
            jMessage' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jMessage
            return jMessage'
    value' <- textToCString value
    g_dbus_message_set_error_name maybeMessage value'
    whenJust message touchManagedPtr
    freeMem value'
    return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetErrorNameMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageSetErrorNameMethodInfo a signature where
    overloadedMethod i = dBusMessageSetErrorName (Just i)

instance O.OverloadedMethodInfo DBusMessageSetErrorNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageSetErrorName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageSetErrorName"
        })


#endif

-- method DBusMessage::set_flags
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "message"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMessage." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessageFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Flags for @message that are set (typically values from the #GDBusMessageFlags\nenumeration bitwise ORed together)."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_message_set_flags" g_dbus_message_set_flags :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "DBusMessageFlags"})
    IO ()

-- | Sets the flags to set on /@message@/.
-- 
-- /Since: 2.26/
dBusMessageSetFlags ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> [Gio.Flags.DBusMessageFlags]
    -- ^ /@flags@/: Flags for /@message@/ that are set (typically values from the t'GI.Gio.Flags.DBusMessageFlags'
    -- enumeration bitwise ORed together).
    -> m ()
dBusMessageSetFlags :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> [DBusMessageFlags] -> m ()
dBusMessageSetFlags a
message [DBusMessageFlags]
flags = 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
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    let flags' = [DBusMessageFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusMessageFlags]
flags
    g_dbus_message_set_flags message' flags'
    touchManagedPtr message
    return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetFlagsMethodInfo
instance (signature ~ ([Gio.Flags.DBusMessageFlags] -> m ()), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageSetFlagsMethodInfo a signature where
    overloadedMethod = dBusMessageSetFlags

instance O.OverloadedMethodInfo DBusMessageSetFlagsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageSetFlags",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageSetFlags"
        })


#endif

-- method DBusMessage::set_header
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "message"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMessage." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "header_field"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusMessageHeaderField" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A 8-bit unsigned integer (typically a value from the #GDBusMessageHeaderField enumeration)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GVariant to set the header field or %NULL to clear the header field."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_message_set_header" g_dbus_message_set_header :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    CUInt ->                                -- header_field : TInterface (Name {namespace = "Gio", name = "DBusMessageHeaderField"})
    Ptr GVariant ->                         -- value : TVariant
    IO ()

-- | Sets a header field on /@message@/.
-- 
-- If /@value@/ is floating, /@message@/ assumes ownership of /@value@/.
-- 
-- /Since: 2.26/
dBusMessageSetHeader ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> Gio.Enums.DBusMessageHeaderField
    -- ^ /@headerField@/: A 8-bit unsigned integer (typically a value from the t'GI.Gio.Enums.DBusMessageHeaderField' enumeration)
    -> Maybe (GVariant)
    -- ^ /@value@/: A t'GVariant' to set the header field or 'P.Nothing' to clear the header field.
    -> m ()
dBusMessageSetHeader :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> DBusMessageHeaderField -> Maybe GVariant -> m ()
dBusMessageSetHeader a
message DBusMessageHeaderField
headerField Maybe GVariant
value = 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
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    let headerField' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (DBusMessageHeaderField -> Int)
-> DBusMessageHeaderField
-> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DBusMessageHeaderField -> Int
forall a. Enum a => a -> Int
fromEnum) DBusMessageHeaderField
headerField
    maybeValue <- case value of
        Maybe GVariant
Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
FP.nullPtr
        Just GVariant
jValue -> do
            jValue' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jValue
            return jValue'
    g_dbus_message_set_header message' headerField' maybeValue
    touchManagedPtr message
    whenJust value touchManagedPtr
    return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetHeaderMethodInfo
instance (signature ~ (Gio.Enums.DBusMessageHeaderField -> Maybe (GVariant) -> m ()), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageSetHeaderMethodInfo a signature where
    overloadedMethod = dBusMessageSetHeader

instance O.OverloadedMethodInfo DBusMessageSetHeaderMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageSetHeader",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageSetHeader"
        })


#endif

-- method DBusMessage::set_interface
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "message"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMessage." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The value to set." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_message_set_interface" g_dbus_message_set_interface :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    CString ->                              -- value : TBasicType TUTF8
    IO ()

-- | Convenience setter for the 'GI.Gio.Enums.DBusMessageHeaderFieldInterface' header field.
-- 
-- /Since: 2.26/
dBusMessageSetInterface ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> Maybe (T.Text)
    -- ^ /@value@/: The value to set.
    -> m ()
dBusMessageSetInterface :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> Maybe Text -> m ()
dBusMessageSetInterface a
message Maybe Text
value = 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
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    maybeValue <- case value of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
FP.nullPtr
        Just Text
jValue -> do
            jValue' <- Text -> IO (Ptr CChar)
textToCString Text
jValue
            return jValue'
    g_dbus_message_set_interface message' maybeValue
    touchManagedPtr message
    freeMem maybeValue
    return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetInterfaceMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageSetInterfaceMethodInfo a signature where
    overloadedMethod = dBusMessageSetInterface

instance O.OverloadedMethodInfo DBusMessageSetInterfaceMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageSetInterface",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageSetInterface"
        })


#endif

-- method DBusMessage::set_member
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "message"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMessage." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The value to set." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_message_set_member" g_dbus_message_set_member :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    CString ->                              -- value : TBasicType TUTF8
    IO ()

-- | Convenience setter for the 'GI.Gio.Enums.DBusMessageHeaderFieldMember' header field.
-- 
-- /Since: 2.26/
dBusMessageSetMember ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> Maybe (T.Text)
    -- ^ /@value@/: The value to set.
    -> m ()
dBusMessageSetMember :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> Maybe Text -> m ()
dBusMessageSetMember a
message Maybe Text
value = 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
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    maybeValue <- case value of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
FP.nullPtr
        Just Text
jValue -> do
            jValue' <- Text -> IO (Ptr CChar)
textToCString Text
jValue
            return jValue'
    g_dbus_message_set_member message' maybeValue
    touchManagedPtr message
    freeMem maybeValue
    return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetMemberMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageSetMemberMethodInfo a signature where
    overloadedMethod = dBusMessageSetMember

instance O.OverloadedMethodInfo DBusMessageSetMemberMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageSetMember",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageSetMember"
        })


#endif

-- method DBusMessage::set_message_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "message"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMessage." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessageType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A 8-bit unsigned integer (typically a value from the #GDBusMessageType enumeration)."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_message_set_message_type" g_dbus_message_set_message_type :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    CUInt ->                                -- type : TInterface (Name {namespace = "Gio", name = "DBusMessageType"})
    IO ()

-- | Sets /@message@/ to be of /@type@/.
-- 
-- /Since: 2.26/
dBusMessageSetMessageType ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> Gio.Enums.DBusMessageType
    -- ^ /@type@/: A 8-bit unsigned integer (typically a value from the t'GI.Gio.Enums.DBusMessageType' enumeration).
    -> m ()
dBusMessageSetMessageType :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> DBusMessageType -> m ()
dBusMessageSetMessageType a
message DBusMessageType
type_ = 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
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    let type_' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (DBusMessageType -> Int) -> DBusMessageType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DBusMessageType -> Int
forall a. Enum a => a -> Int
fromEnum) DBusMessageType
type_
    g_dbus_message_set_message_type message' type_'
    touchManagedPtr message
    return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetMessageTypeMethodInfo
instance (signature ~ (Gio.Enums.DBusMessageType -> m ()), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageSetMessageTypeMethodInfo a signature where
    overloadedMethod = dBusMessageSetMessageType

instance O.OverloadedMethodInfo DBusMessageSetMessageTypeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageSetMessageType",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageSetMessageType"
        })


#endif

-- method DBusMessage::set_num_unix_fds
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "message"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMessage." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The value to set." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_message_set_num_unix_fds" g_dbus_message_set_num_unix_fds :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    Word32 ->                               -- value : TBasicType TUInt32
    IO ()

-- | Convenience setter for the 'GI.Gio.Enums.DBusMessageHeaderFieldNumUnixFds' header field.
-- 
-- /Since: 2.26/
dBusMessageSetNumUnixFds ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> Word32
    -- ^ /@value@/: The value to set.
    -> m ()
dBusMessageSetNumUnixFds :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> Word32 -> m ()
dBusMessageSetNumUnixFds a
message Word32
value = 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
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    g_dbus_message_set_num_unix_fds message' value
    touchManagedPtr message
    return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetNumUnixFdsMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageSetNumUnixFdsMethodInfo a signature where
    overloadedMethod = dBusMessageSetNumUnixFds

instance O.OverloadedMethodInfo DBusMessageSetNumUnixFdsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageSetNumUnixFds",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageSetNumUnixFds"
        })


#endif

-- method DBusMessage::set_path
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "message"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMessage." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The value to set." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_message_set_path" g_dbus_message_set_path :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    CString ->                              -- value : TBasicType TUTF8
    IO ()

-- | Convenience setter for the 'GI.Gio.Enums.DBusMessageHeaderFieldPath' header field.
-- 
-- /Since: 2.26/
dBusMessageSetPath ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> Maybe (T.Text)
    -- ^ /@value@/: The value to set.
    -> m ()
dBusMessageSetPath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> Maybe Text -> m ()
dBusMessageSetPath a
message Maybe Text
value = 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
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    maybeValue <- case value of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
FP.nullPtr
        Just Text
jValue -> do
            jValue' <- Text -> IO (Ptr CChar)
textToCString Text
jValue
            return jValue'
    g_dbus_message_set_path message' maybeValue
    touchManagedPtr message
    freeMem maybeValue
    return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetPathMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageSetPathMethodInfo a signature where
    overloadedMethod = dBusMessageSetPath

instance O.OverloadedMethodInfo DBusMessageSetPathMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageSetPath",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageSetPath"
        })


#endif

-- method DBusMessage::set_reply_serial
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "message"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMessage." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The value to set." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_message_set_reply_serial" g_dbus_message_set_reply_serial :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    Word32 ->                               -- value : TBasicType TUInt32
    IO ()

-- | Convenience setter for the 'GI.Gio.Enums.DBusMessageHeaderFieldReplySerial' header field.
-- 
-- /Since: 2.26/
dBusMessageSetReplySerial ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> Word32
    -- ^ /@value@/: The value to set.
    -> m ()
dBusMessageSetReplySerial :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> Word32 -> m ()
dBusMessageSetReplySerial a
message Word32
value = 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
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    g_dbus_message_set_reply_serial message' value
    touchManagedPtr message
    return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetReplySerialMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageSetReplySerialMethodInfo a signature where
    overloadedMethod = dBusMessageSetReplySerial

instance O.OverloadedMethodInfo DBusMessageSetReplySerialMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageSetReplySerial",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageSetReplySerial"
        })


#endif

-- method DBusMessage::set_sender
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "message"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMessage." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The value to set." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_message_set_sender" g_dbus_message_set_sender :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    CString ->                              -- value : TBasicType TUTF8
    IO ()

-- | Convenience setter for the 'GI.Gio.Enums.DBusMessageHeaderFieldSender' header field.
-- 
-- /Since: 2.26/
dBusMessageSetSender ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> Maybe (T.Text)
    -- ^ /@value@/: The value to set.
    -> m ()
dBusMessageSetSender :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> Maybe Text -> m ()
dBusMessageSetSender a
message Maybe Text
value = 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
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    maybeValue <- case value of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
FP.nullPtr
        Just Text
jValue -> do
            jValue' <- Text -> IO (Ptr CChar)
textToCString Text
jValue
            return jValue'
    g_dbus_message_set_sender message' maybeValue
    touchManagedPtr message
    freeMem maybeValue
    return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetSenderMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageSetSenderMethodInfo a signature where
    overloadedMethod = dBusMessageSetSender

instance O.OverloadedMethodInfo DBusMessageSetSenderMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageSetSender",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageSetSender"
        })


#endif

-- method DBusMessage::set_serial
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "message"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMessage." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "serial"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #guint32." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_message_set_serial" g_dbus_message_set_serial :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    Word32 ->                               -- serial : TBasicType TUInt32
    IO ()

-- | Sets the serial for /@message@/.
-- 
-- /Since: 2.26/
dBusMessageSetSerial ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> Word32
    -- ^ /@serial@/: A @/guint32/@.
    -> m ()
dBusMessageSetSerial :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> Word32 -> m ()
dBusMessageSetSerial a
message Word32
serial = 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
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    g_dbus_message_set_serial message' serial
    touchManagedPtr message
    return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetSerialMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageSetSerialMethodInfo a signature where
    overloadedMethod = dBusMessageSetSerial

instance O.OverloadedMethodInfo DBusMessageSetSerialMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageSetSerial",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageSetSerial"
        })


#endif

-- method DBusMessage::set_signature
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "message"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMessage." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The value to set." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_message_set_signature" g_dbus_message_set_signature :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    CString ->                              -- value : TBasicType TUTF8
    IO ()

-- | Convenience setter for the 'GI.Gio.Enums.DBusMessageHeaderFieldSignature' header field.
-- 
-- /Since: 2.26/
dBusMessageSetSignature ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> Maybe (T.Text)
    -- ^ /@value@/: The value to set.
    -> m ()
dBusMessageSetSignature :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> Maybe Text -> m ()
dBusMessageSetSignature a
message Maybe Text
value = 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
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    maybeValue <- case value of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
FP.nullPtr
        Just Text
jValue -> do
            jValue' <- Text -> IO (Ptr CChar)
textToCString Text
jValue
            return jValue'
    g_dbus_message_set_signature message' maybeValue
    touchManagedPtr message
    freeMem maybeValue
    return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetSignatureMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageSetSignatureMethodInfo a signature where
    overloadedMethod = dBusMessageSetSignature

instance O.OverloadedMethodInfo DBusMessageSetSignatureMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageSetSignature",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageSetSignature"
        })


#endif

-- method DBusMessage::set_unix_fd_list
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "message"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMessage." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_message_set_unix_fd_list" g_dbus_message_set_unix_fd_list :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    Ptr Gio.UnixFDList.UnixFDList ->        -- fd_list : TInterface (Name {namespace = "Gio", name = "UnixFDList"})
    IO ()

-- | Sets the UNIX file descriptors associated with /@message@/. As a
-- side-effect the 'GI.Gio.Enums.DBusMessageHeaderFieldNumUnixFds' header
-- field is set to the number of fds in /@fdList@/ (or cleared if
-- /@fdList@/ is 'P.Nothing').
-- 
-- This method is only available on UNIX.
-- 
-- When designing D-Bus APIs that are intended to be interoperable,
-- please note that non-GDBus implementations of D-Bus can usually only
-- access file descriptors if they are referenced by a value of type
-- @/G_VARIANT_TYPE_HANDLE/@ in the body of the message.
-- 
-- /Since: 2.26/
dBusMessageSetUnixFdList ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a, Gio.UnixFDList.IsUnixFDList b) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> Maybe (b)
    -- ^ /@fdList@/: A t'GI.Gio.Objects.UnixFDList.UnixFDList' or 'P.Nothing'.
    -> m ()
dBusMessageSetUnixFdList :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDBusMessage a, IsUnixFDList b) =>
a -> Maybe b -> m ()
dBusMessageSetUnixFdList a
message Maybe b
fdList = 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
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    maybeFdList <- case fdList of
        Maybe b
Nothing -> Ptr UnixFDList -> IO (Ptr UnixFDList)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr UnixFDList
forall a. Ptr a
FP.nullPtr
        Just b
jFdList -> do
            jFdList' <- b -> IO (Ptr UnixFDList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jFdList
            return jFdList'
    g_dbus_message_set_unix_fd_list message' maybeFdList
    touchManagedPtr message
    whenJust fdList touchManagedPtr
    return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetUnixFdListMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsDBusMessage a, Gio.UnixFDList.IsUnixFDList b) => O.OverloadedMethod DBusMessageSetUnixFdListMethodInfo a signature where
    overloadedMethod = dBusMessageSetUnixFdList

instance O.OverloadedMethodInfo DBusMessageSetUnixFdListMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageSetUnixFdList",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageSetUnixFdList"
        })


#endif

-- method DBusMessage::to_blob
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "message"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DBusMessage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GDBusMessage." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_size"
--           , argType = TBasicType TSize
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Return location for size of generated blob."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "capabilities"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DBusCapabilityFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "A #GDBusCapabilityFlags describing what protocol features are supported."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "out_size"
--              , argType = TBasicType TSize
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "Return location for size of generated blob."
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , argCallbackUserData = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just (TCArray False (-1) 1 (TBasicType TUInt8))
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_message_to_blob" g_dbus_message_to_blob :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    Ptr FCT.CSize ->                        -- out_size : TBasicType TSize
    CUInt ->                                -- capabilities : TInterface (Name {namespace = "Gio", name = "DBusCapabilityFlags"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Word8)

-- | Serializes /@message@/ to a blob. The byte order returned by
-- 'GI.Gio.Objects.DBusMessage.dBusMessageGetByteOrder' will be used.
-- 
-- /Since: 2.26/
dBusMessageToBlob ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> [Gio.Flags.DBusCapabilityFlags]
    -- ^ /@capabilities@/: A t'GI.Gio.Flags.DBusCapabilityFlags' describing what protocol features are supported.
    -> m ByteString
    -- ^ __Returns:__ A pointer to a
    -- valid binary D-Bus message of /@outSize@/ bytes generated by /@message@/
    -- or 'P.Nothing' if /@error@/ is set. Free with 'GI.GLib.Functions.free'. /(Can throw 'Data.GI.Base.GError.GError')/
dBusMessageToBlob :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> [DBusCapabilityFlags] -> m ByteString
dBusMessageToBlob a
message [DBusCapabilityFlags]
capabilities = IO ByteString -> m ByteString
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ByteString -> m ByteString) -> IO ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ do
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    outSize <- allocMem :: IO (Ptr FCT.CSize)
    let capabilities' = [DBusCapabilityFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusCapabilityFlags]
capabilities
    onException (do
        result <- propagateGError $ g_dbus_message_to_blob message' outSize capabilities'
        outSize' <- peek outSize
        checkUnexpectedReturnNULL "dBusMessageToBlob" result
        result' <- (unpackByteStringWithLength outSize') result
        freeMem result
        touchManagedPtr message
        freeMem outSize
        return result'
     ) (do
        freeMem outSize
     )

#if defined(ENABLE_OVERLOADING)
data DBusMessageToBlobMethodInfo
instance (signature ~ ([Gio.Flags.DBusCapabilityFlags] -> m ByteString), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageToBlobMethodInfo a signature where
    overloadedMethod = dBusMessageToBlob

instance O.OverloadedMethodInfo DBusMessageToBlobMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageToBlob",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageToBlob"
        })


#endif

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

foreign import ccall "g_dbus_message_to_gerror" g_dbus_message_to_gerror :: 
    Ptr DBusMessage ->                      -- message : TInterface (Name {namespace = "Gio", name = "DBusMessage"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | If /@message@/ is not of type 'GI.Gio.Enums.DBusMessageTypeError' does
-- nothing and returns 'P.False'.
-- 
-- Otherwise this method encodes the error in /@message@/ as a t'GError'
-- using @/g_dbus_error_set_dbus_error()/@ using the information in the
-- 'GI.Gio.Enums.DBusMessageHeaderFieldErrorName' header field of /@message@/ as
-- well as the first string item in /@message@/\'s body.
-- 
-- /Since: 2.26/
dBusMessageToGerror ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
dBusMessageToGerror :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDBusMessage a) =>
a -> m ()
dBusMessageToGerror a
message = 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
    message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    onException (do
        _ <- propagateGError $ g_dbus_message_to_gerror message'
        touchManagedPtr message
        return ()
     ) (do
        return ()
     )

#if defined(ENABLE_OVERLOADING)
data DBusMessageToGerrorMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDBusMessage a) => O.OverloadedMethod DBusMessageToGerrorMethodInfo a signature where
    overloadedMethod = dBusMessageToGerror

instance O.OverloadedMethodInfo DBusMessageToGerrorMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DBusMessage.dBusMessageToGerror",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DBusMessage.html#v:dBusMessageToGerror"
        })


#endif

-- method DBusMessage::bytes_needed
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "blob"
--           , argType = TCArray False (-1) 1 (TBasicType TUInt8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A blob representing a binary D-Bus message."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "blob_len"
--           , argType = TBasicType TSize
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of @blob (must be at least 16)."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "blob_len"
--              , argType = TBasicType TSize
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "The length of @blob (must be at least 16)."
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , argCallbackUserData = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TBasicType TSSize)
-- throws : True
-- Skip return : False

foreign import ccall "g_dbus_message_bytes_needed" g_dbus_message_bytes_needed :: 
    Ptr Word8 ->                            -- blob : TCArray False (-1) 1 (TBasicType TUInt8)
    FCT.CSize ->                            -- blob_len : TBasicType TSize
    Ptr (Ptr GError) ->                     -- error
    IO DI.Int64

-- | Utility function to calculate how many bytes are needed to
-- completely deserialize the D-Bus message stored at /@blob@/.
-- 
-- /Since: 2.26/
dBusMessageBytesNeeded ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    ByteString
    -- ^ /@blob@/: A blob representing a binary D-Bus message.
    -> m DI.Int64
    -- ^ __Returns:__ Number of bytes needed or -1 if /@error@/ is set (e.g. if
    -- /@blob@/ contains invalid data or not enough data is available to
    -- determine the size). /(Can throw 'Data.GI.Base.GError.GError')/
dBusMessageBytesNeeded :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ByteString -> m Int64
dBusMessageBytesNeeded ByteString
blob = IO Int64 -> m Int64
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int64 -> m Int64) -> IO Int64 -> m Int64
forall a b. (a -> b) -> a -> b
$ do
    let blobLen :: CSize
blobLen = Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CSize) -> Int -> CSize
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
blob
    blob' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
blob
    onException (do
        result <- propagateGError $ g_dbus_message_bytes_needed blob' blobLen
        freeMem blob'
        return result
     ) (do
        freeMem blob'
     )

#if defined(ENABLE_OVERLOADING)
#endif