{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- 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                           ,
    noDBusMessage                           ,


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

#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                      ,


-- ** 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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

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

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

instance GObject DBusMessage where
    gobjectType :: IO GType
gobjectType = IO GType
c_g_dbus_message_get_type
    

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

-- | Type class for types which can be safely cast to `DBusMessage`, for instance with `toDBusMessage`.
class (GObject o, O.IsDescendantOf DBusMessage o) => IsDBusMessage o
instance (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 :: (MonadIO m, IsDBusMessage o) => o -> m DBusMessage
toDBusMessage :: o -> m DBusMessage
toDBusMessage = IO DBusMessage -> m DBusMessage
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr DBusMessage -> DBusMessage
DBusMessage

-- | A convenience alias for `Nothing` :: `Maybe` `DBusMessage`.
noDBusMessage :: Maybe DBusMessage
noDBusMessage :: Maybe DBusMessage
noDBusMessage = Maybe DBusMessage
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveDBusMessageMethod (t :: Symbol) (o :: *) :: * 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 "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.MethodInfo 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

#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 :: o -> m Bool
getDBusMessageLocked obj :: o
obj = IO Bool -> m Bool
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
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "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
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DBusMessage
type instance O.AttributeList DBusMessage = DBusMessageAttributeList
type DBusMessageAttributeList = ('[ '("locked", DBusMessageLockedPropertyInfo)] :: [(Symbol, *)])
#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, *)])

#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 :: m DBusMessage
dBusMessageNew  = IO DBusMessage -> m DBusMessage
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusMessage -> m DBusMessage)
-> IO DBusMessage -> m DBusMessage
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
result <- IO (Ptr DBusMessage)
g_dbus_message_new
    Text -> Ptr DBusMessage -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMessageNew" Ptr DBusMessage
result
    DBusMessage
result' <- ((ManagedPtr DBusMessage -> DBusMessage)
-> Ptr DBusMessage -> IO DBusMessage
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DBusMessage -> DBusMessage
DBusMessage) Ptr DBusMessage
result
    DBusMessage -> IO DBusMessage
forall (m :: * -> *) a. Monad m => a -> m a
return DBusMessage
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
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "blob_len"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The length of @blob."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = 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
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "blob_len"
--              , argType = TBasicType TUInt64
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "The length of @blob."
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = 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)
    Word64 ->                               -- blob_len : TBasicType TUInt64
    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 :: ByteString -> [DBusCapabilityFlags] -> m DBusMessage
dBusMessageNewFromBlob blob :: ByteString
blob capabilities :: [DBusCapabilityFlags]
capabilities = IO DBusMessage -> m DBusMessage
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusMessage -> m DBusMessage)
-> IO DBusMessage -> m DBusMessage
forall a b. (a -> b) -> a -> b
$ do
    let blobLen :: Word64
blobLen = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
blob
    Ptr Word8
blob' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
blob
    let capabilities' :: CUInt
capabilities' = [DBusCapabilityFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusCapabilityFlags]
capabilities
    IO DBusMessage -> IO () -> IO DBusMessage
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr DBusMessage
result <- (Ptr (Ptr GError) -> IO (Ptr DBusMessage)) -> IO (Ptr DBusMessage)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr DBusMessage))
 -> IO (Ptr DBusMessage))
-> (Ptr (Ptr GError) -> IO (Ptr DBusMessage))
-> IO (Ptr DBusMessage)
forall a b. (a -> b) -> a -> b
$ Ptr Word8
-> Word64 -> CUInt -> Ptr (Ptr GError) -> IO (Ptr DBusMessage)
g_dbus_message_new_from_blob Ptr Word8
blob' Word64
blobLen CUInt
capabilities'
        Text -> Ptr DBusMessage -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMessageNewFromBlob" Ptr DBusMessage
result
        DBusMessage
result' <- ((ManagedPtr DBusMessage -> DBusMessage)
-> Ptr DBusMessage -> IO DBusMessage
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DBusMessage -> DBusMessage
DBusMessage) Ptr DBusMessage
result
        Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
blob'
        DBusMessage -> IO DBusMessage
forall (m :: * -> *) a. Monad m => a -> m a
return DBusMessage
result'
     ) (do
        Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
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
--           , 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
--           , 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
--           , 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
--           , 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 :: Maybe Text -> Text -> Maybe Text -> Text -> m DBusMessage
dBusMessageNewMethodCall name :: Maybe Text
name path :: Text
path interface_ :: Maybe Text
interface_ method :: Text
method = IO DBusMessage -> m DBusMessage
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusMessage -> m DBusMessage)
-> IO DBusMessage -> m DBusMessage
forall a b. (a -> b) -> a -> b
$ do
    Ptr CChar
maybeName <- case Maybe Text
name of
        Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just jName :: Text
jName -> do
            Ptr CChar
jName' <- Text -> IO (Ptr CChar)
textToCString Text
jName
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jName'
    Ptr CChar
path' <- Text -> IO (Ptr CChar)
textToCString Text
path
    Ptr CChar
maybeInterface_ <- case Maybe Text
interface_ of
        Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just jInterface_ :: Text
jInterface_ -> do
            Ptr CChar
jInterface_' <- Text -> IO (Ptr CChar)
textToCString Text
jInterface_
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jInterface_'
    Ptr CChar
method' <- Text -> IO (Ptr CChar)
textToCString Text
method
    Ptr DBusMessage
result <- Ptr CChar
-> Ptr CChar -> Ptr CChar -> Ptr CChar -> IO (Ptr DBusMessage)
g_dbus_message_new_method_call Ptr CChar
maybeName Ptr CChar
path' Ptr CChar
maybeInterface_ Ptr CChar
method'
    Text -> Ptr DBusMessage -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMessageNewMethodCall" Ptr DBusMessage
result
    DBusMessage
result' <- ((ManagedPtr DBusMessage -> DBusMessage)
-> Ptr DBusMessage -> IO DBusMessage
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DBusMessage -> DBusMessage
DBusMessage) Ptr DBusMessage
result
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeName
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
path'
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeInterface_
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
method'
    DBusMessage -> IO DBusMessage
forall (m :: * -> *) a. Monad m => a -> m a
return DBusMessage
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
--           , 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
--           , 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
--           , 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 :: Text -> Text -> Text -> m DBusMessage
dBusMessageNewSignal path :: Text
path interface_ :: Text
interface_ signal :: Text
signal = IO DBusMessage -> m DBusMessage
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusMessage -> m DBusMessage)
-> IO DBusMessage -> m DBusMessage
forall a b. (a -> b) -> a -> b
$ do
    Ptr CChar
path' <- Text -> IO (Ptr CChar)
textToCString Text
path
    Ptr CChar
interface_' <- Text -> IO (Ptr CChar)
textToCString Text
interface_
    Ptr CChar
signal' <- Text -> IO (Ptr CChar)
textToCString Text
signal
    Ptr DBusMessage
result <- Ptr CChar -> Ptr CChar -> Ptr CChar -> IO (Ptr DBusMessage)
g_dbus_message_new_signal Ptr CChar
path' Ptr CChar
interface_' Ptr CChar
signal'
    Text -> Ptr DBusMessage -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMessageNewSignal" Ptr DBusMessage
result
    DBusMessage
result' <- ((ManagedPtr DBusMessage -> DBusMessage)
-> Ptr DBusMessage -> IO DBusMessage
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DBusMessage -> DBusMessage
DBusMessage) Ptr DBusMessage
result
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
path'
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
interface_'
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
signal'
    DBusMessage -> IO DBusMessage
forall (m :: * -> *) a. Monad m => a -> m a
return DBusMessage
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
--           , 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 :: a -> m DBusMessage
dBusMessageCopy message :: a
message = IO DBusMessage -> m DBusMessage
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusMessage -> m DBusMessage)
-> IO DBusMessage -> m DBusMessage
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    IO DBusMessage -> IO () -> IO DBusMessage
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr DBusMessage
result <- (Ptr (Ptr GError) -> IO (Ptr DBusMessage)) -> IO (Ptr DBusMessage)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr DBusMessage))
 -> IO (Ptr DBusMessage))
-> (Ptr (Ptr GError) -> IO (Ptr DBusMessage))
-> IO (Ptr DBusMessage)
forall a b. (a -> b) -> a -> b
$ Ptr DBusMessage -> Ptr (Ptr GError) -> IO (Ptr DBusMessage)
g_dbus_message_copy Ptr DBusMessage
message'
        Text -> Ptr DBusMessage -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMessageCopy" Ptr DBusMessage
result
        DBusMessage
result' <- ((ManagedPtr DBusMessage -> DBusMessage)
-> Ptr DBusMessage -> IO DBusMessage
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DBusMessage -> DBusMessage
DBusMessage) Ptr DBusMessage
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
        DBusMessage -> IO DBusMessage
forall (m :: * -> *) a. Monad m => a -> m a
return DBusMessage
result'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DBusMessageCopyMethodInfo
instance (signature ~ (m DBusMessage), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageCopyMethodInfo a signature where
    overloadedMethod = 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
--           , 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@/.
-- 
-- /Since: 2.26/
dBusMessageGetArg0 ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> m T.Text
    -- ^ __Returns:__ The string item or 'P.Nothing' if the first item in the body of
    -- /@message@/ is not a string.
dBusMessageGetArg0 :: a -> m Text
dBusMessageGetArg0 message :: a
message = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr CChar
result <- Ptr DBusMessage -> IO (Ptr CChar)
g_dbus_message_get_arg0 Ptr DBusMessage
message'
    Text -> Ptr CChar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMessageGetArg0" Ptr CChar
result
    Text
result' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

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

#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
--           , 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 GVariant
    -- ^ __Returns:__ A t'GVariant' or 'P.Nothing' if the body is
    -- empty. Do not free, it is owned by /@message@/.
dBusMessageGetBody :: a -> m GVariant
dBusMessageGetBody message :: a
message = IO GVariant -> m GVariant
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GVariant -> m GVariant) -> IO GVariant -> m GVariant
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr GVariant
result <- Ptr DBusMessage -> IO (Ptr GVariant)
g_dbus_message_get_body Ptr DBusMessage
message'
    Text -> Ptr GVariant -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMessageGetBody" Ptr GVariant
result
    GVariant
result' <- Ptr GVariant -> IO GVariant
B.GVariant.newGVariantFromPtr Ptr GVariant
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    GVariant -> IO GVariant
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result'

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetBodyMethodInfo
instance (signature ~ (m GVariant), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageGetBodyMethodInfo a signature where
    overloadedMethod = 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
--           , 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 :: a -> m DBusMessageByteOrder
dBusMessageGetByteOrder message :: a
message = IO DBusMessageByteOrder -> m DBusMessageByteOrder
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
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    CUInt
result <- Ptr DBusMessage -> IO CUInt
g_dbus_message_get_byte_order Ptr DBusMessage
message'
    let result' :: DBusMessageByteOrder
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
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    DBusMessageByteOrder -> IO DBusMessageByteOrder
forall (m :: * -> *) a. Monad m => a -> m a
return DBusMessageByteOrder
result'

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetByteOrderMethodInfo
instance (signature ~ (m Gio.Enums.DBusMessageByteOrder), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageGetByteOrderMethodInfo a signature where
    overloadedMethod = 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
--           , 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 T.Text
    -- ^ __Returns:__ The value.
dBusMessageGetDestination :: a -> m Text
dBusMessageGetDestination message :: a
message = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr CChar
result <- Ptr DBusMessage -> IO (Ptr CChar)
g_dbus_message_get_destination Ptr DBusMessage
message'
    Text -> Ptr CChar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMessageGetDestination" Ptr CChar
result
    Text
result' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetDestinationMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageGetDestinationMethodInfo a signature where
    overloadedMethod = 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
--           , 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 T.Text
    -- ^ __Returns:__ The value.
dBusMessageGetErrorName :: a -> m Text
dBusMessageGetErrorName message :: a
message = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr CChar
result <- Ptr DBusMessage -> IO (Ptr CChar)
g_dbus_message_get_error_name Ptr DBusMessage
message'
    Text -> Ptr CChar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMessageGetErrorName" Ptr CChar
result
    Text
result' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetErrorNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageGetErrorNameMethodInfo a signature where
    overloadedMethod = 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
--           , 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 :: a -> m [DBusMessageFlags]
dBusMessageGetFlags message :: a
message = IO [DBusMessageFlags] -> m [DBusMessageFlags]
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
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    CUInt
result <- Ptr DBusMessage -> IO CUInt
g_dbus_message_get_flags Ptr DBusMessage
message'
    let result' :: [DBusMessageFlags]
result' = CUInt -> [DBusMessageFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    [DBusMessageFlags] -> IO [DBusMessageFlags]
forall (m :: * -> *) a. Monad m => a -> m a
return [DBusMessageFlags]
result'

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetFlagsMethodInfo
instance (signature ~ (m [Gio.Flags.DBusMessageFlags]), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageGetFlagsMethodInfo a signature where
    overloadedMethod = 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
--           , 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
--           , 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 :: a -> DBusMessageHeaderField -> m (Maybe GVariant)
dBusMessageGetHeader message :: a
message headerField :: DBusMessageHeaderField
headerField = IO (Maybe GVariant) -> m (Maybe GVariant)
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
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    let headerField' :: CUInt
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
    Ptr GVariant
result <- Ptr DBusMessage -> CUInt -> IO (Ptr GVariant)
g_dbus_message_get_header Ptr DBusMessage
message' CUInt
headerField'
    Maybe GVariant
maybeResult <- Ptr GVariant
-> (Ptr GVariant -> IO GVariant) -> IO (Maybe GVariant)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr GVariant
result ((Ptr GVariant -> IO GVariant) -> IO (Maybe GVariant))
-> (Ptr GVariant -> IO GVariant) -> IO (Maybe GVariant)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr GVariant
result' -> do
        GVariant
result'' <- Ptr GVariant -> IO GVariant
B.GVariant.newGVariantFromPtr Ptr GVariant
result'
        GVariant -> IO GVariant
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Maybe GVariant -> IO (Maybe GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GVariant
maybeResult

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetHeaderMethodInfo
instance (signature ~ (Gio.Enums.DBusMessageHeaderField -> m (Maybe GVariant)), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageGetHeaderMethodInfo a signature where
    overloadedMethod = 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
--           , 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 :: a -> m ByteString
dBusMessageGetHeaderFields message :: a
message = IO ByteString -> m ByteString
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
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr Word8
result <- Ptr DBusMessage -> IO (Ptr Word8)
g_dbus_message_get_header_fields Ptr DBusMessage
message'
    Text -> Ptr Word8 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMessageGetHeaderFields" Ptr Word8
result
    ByteString
result' <- Ptr Word8 -> IO ByteString
unpackZeroTerminatedByteString Ptr Word8
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
result'

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetHeaderFieldsMethodInfo
instance (signature ~ (m ByteString), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageGetHeaderFieldsMethodInfo a signature where
    overloadedMethod = 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
--           , 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 T.Text
    -- ^ __Returns:__ The value.
dBusMessageGetInterface :: a -> m Text
dBusMessageGetInterface message :: a
message = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr CChar
result <- Ptr DBusMessage -> IO (Ptr CChar)
g_dbus_message_get_interface Ptr DBusMessage
message'
    Text -> Ptr CChar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMessageGetInterface" Ptr CChar
result
    Text
result' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetInterfaceMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageGetInterfaceMethodInfo a signature where
    overloadedMethod = 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
--           , 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 [notify]("GI.GObject.Objects.Object#signal:notify") signal to listen for changes
-- on the t'GI.Gio.Objects.DBusMessage.DBusMessage':@/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 :: a -> m Bool
dBusMessageGetLocked message :: a
message = IO Bool -> m Bool
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
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    CInt
result <- Ptr DBusMessage -> IO CInt
g_dbus_message_get_locked Ptr DBusMessage
message'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetLockedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageGetLockedMethodInfo a signature where
    overloadedMethod = 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
--           , 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 T.Text
    -- ^ __Returns:__ The value.
dBusMessageGetMember :: a -> m Text
dBusMessageGetMember message :: a
message = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr CChar
result <- Ptr DBusMessage -> IO (Ptr CChar)
g_dbus_message_get_member Ptr DBusMessage
message'
    Text -> Ptr CChar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMessageGetMember" Ptr CChar
result
    Text
result' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetMemberMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageGetMemberMethodInfo a signature where
    overloadedMethod = 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
--           , 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 :: a -> m DBusMessageType
dBusMessageGetMessageType message :: a
message = IO DBusMessageType -> m DBusMessageType
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
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    CUInt
result <- Ptr DBusMessage -> IO CUInt
g_dbus_message_get_message_type Ptr DBusMessage
message'
    let result' :: DBusMessageType
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
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    DBusMessageType -> IO DBusMessageType
forall (m :: * -> *) a. Monad m => a -> m a
return DBusMessageType
result'

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetMessageTypeMethodInfo
instance (signature ~ (m Gio.Enums.DBusMessageType), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageGetMessageTypeMethodInfo a signature where
    overloadedMethod = 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
--           , 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 :: a -> m Word32
dBusMessageGetNumUnixFds message :: a
message = IO Word32 -> m Word32
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
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Word32
result <- Ptr DBusMessage -> IO Word32
g_dbus_message_get_num_unix_fds Ptr DBusMessage
message'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetNumUnixFdsMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageGetNumUnixFdsMethodInfo a signature where
    overloadedMethod = 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
--           , 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 T.Text
    -- ^ __Returns:__ The value.
dBusMessageGetPath :: a -> m Text
dBusMessageGetPath message :: a
message = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr CChar
result <- Ptr DBusMessage -> IO (Ptr CChar)
g_dbus_message_get_path Ptr DBusMessage
message'
    Text -> Ptr CChar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMessageGetPath" Ptr CChar
result
    Text
result' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetPathMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageGetPathMethodInfo a signature where
    overloadedMethod = 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
--           , 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 :: a -> m Word32
dBusMessageGetReplySerial message :: a
message = IO Word32 -> m Word32
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
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Word32
result <- Ptr DBusMessage -> IO Word32
g_dbus_message_get_reply_serial Ptr DBusMessage
message'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetReplySerialMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageGetReplySerialMethodInfo a signature where
    overloadedMethod = 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
--           , 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 T.Text
    -- ^ __Returns:__ The value.
dBusMessageGetSender :: a -> m Text
dBusMessageGetSender message :: a
message = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr CChar
result <- Ptr DBusMessage -> IO (Ptr CChar)
g_dbus_message_get_sender Ptr DBusMessage
message'
    Text -> Ptr CChar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMessageGetSender" Ptr CChar
result
    Text
result' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetSenderMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageGetSenderMethodInfo a signature where
    overloadedMethod = 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
--           , 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 :: a -> m Word32
dBusMessageGetSerial message :: a
message = IO Word32 -> m Word32
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
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Word32
result <- Ptr DBusMessage -> IO Word32
g_dbus_message_get_serial Ptr DBusMessage
message'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetSerialMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageGetSerialMethodInfo a signature where
    overloadedMethod = 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
--           , 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.
-- 
-- /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 :: a -> m Text
dBusMessageGetSignature message :: a
message = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr CChar
result <- Ptr DBusMessage -> IO (Ptr CChar)
g_dbus_message_get_signature Ptr DBusMessage
message'
    Text -> Ptr CChar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMessageGetSignature" Ptr CChar
result
    Text
result' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetSignatureMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageGetSignatureMethodInfo a signature where
    overloadedMethod = 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
--           , 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.
-- 
-- /Since: 2.26/
dBusMessageGetUnixFdList ::
    (B.CallStack.HasCallStack, MonadIO m, IsDBusMessage a) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> m 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 :: a -> m UnixFDList
dBusMessageGetUnixFdList message :: a
message = IO UnixFDList -> m UnixFDList
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO UnixFDList -> m UnixFDList) -> IO UnixFDList -> m UnixFDList
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr UnixFDList
result <- Ptr DBusMessage -> IO (Ptr UnixFDList)
g_dbus_message_get_unix_fd_list Ptr DBusMessage
message'
    Text -> Ptr UnixFDList -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMessageGetUnixFdList" Ptr UnixFDList
result
    UnixFDList
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
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    UnixFDList -> IO UnixFDList
forall (m :: * -> *) a. Monad m => a -> m a
return UnixFDList
result'

#if defined(ENABLE_OVERLOADING)
data DBusMessageGetUnixFdListMethodInfo
instance (signature ~ (m Gio.UnixFDList.UnixFDList), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageGetUnixFdListMethodInfo a signature where
    overloadedMethod = 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
--           , 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 :: a -> m ()
dBusMessageLock message :: a
message = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr DBusMessage -> IO ()
g_dbus_message_lock Ptr DBusMessage
message'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageLockMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageLockMethodInfo a signature where
    overloadedMethod = 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
--           , 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
--           , 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
--           , 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 :: a -> Text -> Text -> m DBusMessage
dBusMessageNewMethodErrorLiteral methodCallMessage :: a
methodCallMessage errorName :: Text
errorName errorMessage :: Text
errorMessage = IO DBusMessage -> m DBusMessage
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusMessage -> m DBusMessage)
-> IO DBusMessage -> m DBusMessage
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
methodCallMessage' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
methodCallMessage
    Ptr CChar
errorName' <- Text -> IO (Ptr CChar)
textToCString Text
errorName
    Ptr CChar
errorMessage' <- Text -> IO (Ptr CChar)
textToCString Text
errorMessage
    Ptr DBusMessage
result <- Ptr DBusMessage -> Ptr CChar -> Ptr CChar -> IO (Ptr DBusMessage)
g_dbus_message_new_method_error_literal Ptr DBusMessage
methodCallMessage' Ptr CChar
errorName' Ptr CChar
errorMessage'
    Text -> Ptr DBusMessage -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMessageNewMethodErrorLiteral" Ptr DBusMessage
result
    DBusMessage
result' <- ((ManagedPtr DBusMessage -> DBusMessage)
-> Ptr DBusMessage -> IO DBusMessage
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DBusMessage -> DBusMessage
DBusMessage) Ptr DBusMessage
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
methodCallMessage
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
errorName'
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
errorMessage'
    DBusMessage -> IO DBusMessage
forall (m :: * -> *) a. Monad m => a -> m a
return DBusMessage
result'

#if defined(ENABLE_OVERLOADING)
data DBusMessageNewMethodErrorLiteralMethodInfo
instance (signature ~ (T.Text -> T.Text -> m DBusMessage), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageNewMethodErrorLiteralMethodInfo a signature where
    overloadedMethod = 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
--           , 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 :: a -> m DBusMessage
dBusMessageNewMethodReply methodCallMessage :: a
methodCallMessage = IO DBusMessage -> m DBusMessage
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusMessage -> m DBusMessage)
-> IO DBusMessage -> m DBusMessage
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
methodCallMessage' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
methodCallMessage
    Ptr DBusMessage
result <- Ptr DBusMessage -> IO (Ptr DBusMessage)
g_dbus_message_new_method_reply Ptr DBusMessage
methodCallMessage'
    Text -> Ptr DBusMessage -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMessageNewMethodReply" Ptr DBusMessage
result
    DBusMessage
result' <- ((ManagedPtr DBusMessage -> DBusMessage)
-> Ptr DBusMessage -> IO DBusMessage
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DBusMessage -> DBusMessage
DBusMessage) Ptr DBusMessage
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
methodCallMessage
    DBusMessage -> IO DBusMessage
forall (m :: * -> *) a. Monad m => a -> m a
return DBusMessage
result'

#if defined(ENABLE_OVERLOADING)
data DBusMessageNewMethodReplyMethodInfo
instance (signature ~ (m DBusMessage), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageNewMethodReplyMethodInfo a signature where
    overloadedMethod = 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
--           , 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
--           , 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 :: a -> Word32 -> m Text
dBusMessagePrint message :: a
message indent :: Word32
indent = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr CChar
result <- Ptr DBusMessage -> Word32 -> IO (Ptr CChar)
g_dbus_message_print Ptr DBusMessage
message' Word32
indent
    Text -> Ptr CChar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMessagePrint" Ptr CChar
result
    Text
result' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DBusMessagePrintMethodInfo
instance (signature ~ (Word32 -> m T.Text), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessagePrintMethodInfo a signature where
    overloadedMethod = 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
--           , 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
--           , 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 :: a -> GVariant -> m ()
dBusMessageSetBody message :: a
message body :: GVariant
body = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr GVariant
body' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
body
    Ptr DBusMessage -> Ptr GVariant -> IO ()
g_dbus_message_set_body Ptr DBusMessage
message' Ptr GVariant
body'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GVariant
body
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetBodyMethodInfo
instance (signature ~ (GVariant -> m ()), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageSetBodyMethodInfo a signature where
    overloadedMethod = 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
--           , 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
--           , 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 :: a -> DBusMessageByteOrder -> m ()
dBusMessageSetByteOrder message :: a
message byteOrder :: DBusMessageByteOrder
byteOrder = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    let byteOrder' :: CUInt
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
    Ptr DBusMessage -> CUInt -> IO ()
g_dbus_message_set_byte_order Ptr DBusMessage
message' CUInt
byteOrder'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetByteOrderMethodInfo
instance (signature ~ (Gio.Enums.DBusMessageByteOrder -> m ()), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageSetByteOrderMethodInfo a signature where
    overloadedMethod = 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
--           , 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
--           , 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'.
    -> T.Text
    -- ^ /@value@/: The value to set.
    -> m ()
dBusMessageSetDestination :: a -> Text -> m ()
dBusMessageSetDestination message :: a
message value :: Text
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr CChar
value' <- Text -> IO (Ptr CChar)
textToCString Text
value
    Ptr DBusMessage -> Ptr CChar -> IO ()
g_dbus_message_set_destination Ptr DBusMessage
message' Ptr CChar
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
value'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

#endif

-- method DBusMessage::set_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
--           , 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
--           , 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) =>
    a
    -- ^ /@message@/: A t'GI.Gio.Objects.DBusMessage.DBusMessage'.
    -> T.Text
    -- ^ /@value@/: The value to set.
    -> m ()
dBusMessageSetErrorName :: a -> Text -> m ()
dBusMessageSetErrorName message :: a
message value :: Text
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr CChar
value' <- Text -> IO (Ptr CChar)
textToCString Text
value
    Ptr DBusMessage -> Ptr CChar -> IO ()
g_dbus_message_set_error_name Ptr DBusMessage
message' Ptr CChar
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
value'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetErrorNameMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageSetErrorNameMethodInfo a signature where
    overloadedMethod = 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
--           , 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
--           , 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 :: a -> [DBusMessageFlags] -> m ()
dBusMessageSetFlags message :: a
message flags :: [DBusMessageFlags]
flags = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    let flags' :: CUInt
flags' = [DBusMessageFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusMessageFlags]
flags
    Ptr DBusMessage -> CUInt -> IO ()
g_dbus_message_set_flags Ptr DBusMessage
message' CUInt
flags'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetFlagsMethodInfo
instance (signature ~ ([Gio.Flags.DBusMessageFlags] -> m ()), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageSetFlagsMethodInfo a signature where
    overloadedMethod = 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
--           , 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
--           , 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
--           , 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 :: a -> DBusMessageHeaderField -> Maybe GVariant -> m ()
dBusMessageSetHeader message :: a
message headerField :: DBusMessageHeaderField
headerField value :: Maybe GVariant
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    let headerField' :: CUInt
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
    Ptr GVariant
maybeValue <- case Maybe GVariant
value of
        Nothing -> Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
forall a. Ptr a
nullPtr
        Just jValue :: GVariant
jValue -> do
            Ptr GVariant
jValue' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
jValue
            Ptr GVariant -> IO (Ptr GVariant)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr GVariant
jValue'
    Ptr DBusMessage -> CUInt -> Ptr GVariant -> IO ()
g_dbus_message_set_header Ptr DBusMessage
message' CUInt
headerField' Ptr GVariant
maybeValue
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Maybe GVariant -> (GVariant -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe GVariant
value GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetHeaderMethodInfo
instance (signature ~ (Gio.Enums.DBusMessageHeaderField -> Maybe (GVariant) -> m ()), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageSetHeaderMethodInfo a signature where
    overloadedMethod = 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
--           , 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
--           , 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'.
    -> T.Text
    -- ^ /@value@/: The value to set.
    -> m ()
dBusMessageSetInterface :: a -> Text -> m ()
dBusMessageSetInterface message :: a
message value :: Text
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr CChar
value' <- Text -> IO (Ptr CChar)
textToCString Text
value
    Ptr DBusMessage -> Ptr CChar -> IO ()
g_dbus_message_set_interface Ptr DBusMessage
message' Ptr CChar
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
value'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetInterfaceMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageSetInterfaceMethodInfo a signature where
    overloadedMethod = 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
--           , 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
--           , 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'.
    -> T.Text
    -- ^ /@value@/: The value to set.
    -> m ()
dBusMessageSetMember :: a -> Text -> m ()
dBusMessageSetMember message :: a
message value :: Text
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr CChar
value' <- Text -> IO (Ptr CChar)
textToCString Text
value
    Ptr DBusMessage -> Ptr CChar -> IO ()
g_dbus_message_set_member Ptr DBusMessage
message' Ptr CChar
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
value'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetMemberMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageSetMemberMethodInfo a signature where
    overloadedMethod = 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
--           , 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
--           , 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 :: a -> DBusMessageType -> m ()
dBusMessageSetMessageType message :: a
message type_ :: DBusMessageType
type_ = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    let type_' :: CUInt
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_
    Ptr DBusMessage -> CUInt -> IO ()
g_dbus_message_set_message_type Ptr DBusMessage
message' CUInt
type_'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetMessageTypeMethodInfo
instance (signature ~ (Gio.Enums.DBusMessageType -> m ()), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageSetMessageTypeMethodInfo a signature where
    overloadedMethod = 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
--           , 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
--           , 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 :: a -> Word32 -> m ()
dBusMessageSetNumUnixFds message :: a
message value :: Word32
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr DBusMessage -> Word32 -> IO ()
g_dbus_message_set_num_unix_fds Ptr DBusMessage
message' Word32
value
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetNumUnixFdsMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageSetNumUnixFdsMethodInfo a signature where
    overloadedMethod = 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
--           , 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
--           , 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'.
    -> T.Text
    -- ^ /@value@/: The value to set.
    -> m ()
dBusMessageSetPath :: a -> Text -> m ()
dBusMessageSetPath message :: a
message value :: Text
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr CChar
value' <- Text -> IO (Ptr CChar)
textToCString Text
value
    Ptr DBusMessage -> Ptr CChar -> IO ()
g_dbus_message_set_path Ptr DBusMessage
message' Ptr CChar
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
value'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetPathMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageSetPathMethodInfo a signature where
    overloadedMethod = 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
--           , 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
--           , 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 :: a -> Word32 -> m ()
dBusMessageSetReplySerial message :: a
message value :: Word32
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr DBusMessage -> Word32 -> IO ()
g_dbus_message_set_reply_serial Ptr DBusMessage
message' Word32
value
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetReplySerialMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageSetReplySerialMethodInfo a signature where
    overloadedMethod = 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
--           , 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
--           , 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'.
    -> T.Text
    -- ^ /@value@/: The value to set.
    -> m ()
dBusMessageSetSender :: a -> Text -> m ()
dBusMessageSetSender message :: a
message value :: Text
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr CChar
value' <- Text -> IO (Ptr CChar)
textToCString Text
value
    Ptr DBusMessage -> Ptr CChar -> IO ()
g_dbus_message_set_sender Ptr DBusMessage
message' Ptr CChar
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
value'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetSenderMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageSetSenderMethodInfo a signature where
    overloadedMethod = 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
--           , 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
--           , 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 :: a -> Word32 -> m ()
dBusMessageSetSerial message :: a
message serial :: Word32
serial = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr DBusMessage -> Word32 -> IO ()
g_dbus_message_set_serial Ptr DBusMessage
message' Word32
serial
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetSerialMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageSetSerialMethodInfo a signature where
    overloadedMethod = 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
--           , 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
--           , 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'.
    -> T.Text
    -- ^ /@value@/: The value to set.
    -> m ()
dBusMessageSetSignature :: a -> Text -> m ()
dBusMessageSetSignature message :: a
message value :: Text
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr CChar
value' <- Text -> IO (Ptr CChar)
textToCString Text
value
    Ptr DBusMessage -> Ptr CChar -> IO ()
g_dbus_message_set_signature Ptr DBusMessage
message' Ptr CChar
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
value'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetSignatureMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageSetSignatureMethodInfo a signature where
    overloadedMethod = 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
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "fd_list"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "UnixFDList" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GUnixFDList or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_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.
-- 
-- /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 :: a -> Maybe b -> m ()
dBusMessageSetUnixFdList message :: a
message fdList :: Maybe b
fdList = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr UnixFDList
maybeFdList <- case Maybe b
fdList of
        Nothing -> Ptr UnixFDList -> IO (Ptr UnixFDList)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr UnixFDList
forall a. Ptr a
nullPtr
        Just jFdList :: b
jFdList -> do
            Ptr UnixFDList
jFdList' <- b -> IO (Ptr UnixFDList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jFdList
            Ptr UnixFDList -> IO (Ptr UnixFDList)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr UnixFDList
jFdList'
    Ptr DBusMessage -> Ptr UnixFDList -> IO ()
g_dbus_message_set_unix_fd_list Ptr DBusMessage
message' Ptr UnixFDList
maybeFdList
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
fdList b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DBusMessageSetUnixFdListMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsDBusMessage a, Gio.UnixFDList.IsUnixFDList b) => O.MethodInfo DBusMessageSetUnixFdListMethodInfo a signature where
    overloadedMethod = 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
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_size"
--           , argType = TBasicType TUInt64
--           , 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
--           , 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
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "out_size"
--              , argType = TBasicType TUInt64
--              , 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
--              , 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 Word64 ->                           -- out_size : TBasicType TUInt64
    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 :: a -> [DBusCapabilityFlags] -> m ByteString
dBusMessageToBlob message :: a
message capabilities :: [DBusCapabilityFlags]
capabilities = IO ByteString -> m ByteString
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
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    Ptr Word64
outSize <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
    let capabilities' :: CUInt
capabilities' = [DBusCapabilityFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [DBusCapabilityFlags]
capabilities
    IO ByteString -> IO () -> IO ByteString
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Word8
result <- (Ptr (Ptr GError) -> IO (Ptr Word8)) -> IO (Ptr Word8)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Word8)) -> IO (Ptr Word8))
-> (Ptr (Ptr GError) -> IO (Ptr Word8)) -> IO (Ptr Word8)
forall a b. (a -> b) -> a -> b
$ Ptr DBusMessage
-> Ptr Word64 -> CUInt -> Ptr (Ptr GError) -> IO (Ptr Word8)
g_dbus_message_to_blob Ptr DBusMessage
message' Ptr Word64
outSize CUInt
capabilities'
        Word64
outSize' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
outSize
        Text -> Ptr Word8 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "dBusMessageToBlob" Ptr Word8
result
        ByteString
result' <- (Word64 -> Ptr Word8 -> IO ByteString
forall a. Integral a => a -> Ptr Word8 -> IO ByteString
unpackByteStringWithLength Word64
outSize') Ptr Word8
result
        Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
outSize
        ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
result'
     ) (do
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
outSize
     )

#if defined(ENABLE_OVERLOADING)
data DBusMessageToBlobMethodInfo
instance (signature ~ ([Gio.Flags.DBusCapabilityFlags] -> m ByteString), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageToBlobMethodInfo a signature where
    overloadedMethod = 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
--           , 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 :: a -> m ()
dBusMessageToGerror message :: a
message = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DBusMessage
message' <- a -> IO (Ptr DBusMessage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
message
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr DBusMessage -> Ptr (Ptr GError) -> IO CInt
g_dbus_message_to_gerror Ptr DBusMessage
message'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
message
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DBusMessageToGerrorMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDBusMessage a) => O.MethodInfo DBusMessageToGerrorMethodInfo a signature where
    overloadedMethod = 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
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "blob_len"
--           , argType = TBasicType TUInt64
--           , 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
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "blob_len"
--              , argType = TBasicType TUInt64
--              , 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
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TBasicType TInt64)
-- 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)
    Word64 ->                               -- blob_len : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO 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 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 :: ByteString -> m Int64
dBusMessageBytesNeeded blob :: ByteString
blob = IO Int64 -> m Int64
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 :: Word64
blobLen = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
blob
    Ptr Word8
blob' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
blob
    IO Int64 -> IO () -> IO Int64
forall a b. IO a -> IO b -> IO a
onException (do
        Int64
result <- (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Int64) -> IO Int64)
-> (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a b. (a -> b) -> a -> b
$ Ptr Word8 -> Word64 -> Ptr (Ptr GError) -> IO Int64
g_dbus_message_bytes_needed Ptr Word8
blob' Word64
blobLen
        Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
blob'
        Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
result
     ) (do
        Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
blob'
     )

#if defined(ENABLE_OVERLOADING)
#endif