{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)

Information about an argument for a method or a signal.
-}

module GI.Gio.Structs.DBusArgInfo
    ( 

-- * Exported types
    DBusArgInfo(..)                         ,
    noDBusArgInfo                           ,


 -- * Methods
-- ** dBusArgInfoRef
    dBusArgInfoRef                          ,


-- ** dBusArgInfoUnref
    dBusArgInfoUnref                        ,




 -- * Properties
-- ** Annotations
    dBusArgInfoReadAnnotations              ,


-- ** Name
    dBusArgInfoReadName                     ,


-- ** RefCount
    dBusArgInfoReadRefCount                 ,


-- ** Signature
    dBusArgInfoReadSignature                ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.Gio.Types
import GI.Gio.Callbacks

newtype DBusArgInfo = DBusArgInfo (ForeignPtr DBusArgInfo)
foreign import ccall "g_dbus_arg_info_get_type" c_g_dbus_arg_info_get_type :: 
    IO GType

instance BoxedObject DBusArgInfo where
    boxedType _ = c_g_dbus_arg_info_get_type

noDBusArgInfo :: Maybe DBusArgInfo
noDBusArgInfo = Nothing

dBusArgInfoReadRefCount :: DBusArgInfo -> IO Int32
dBusArgInfoReadRefCount s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO Int32
    return val

dBusArgInfoReadName :: DBusArgInfo -> IO T.Text
dBusArgInfoReadName s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO CString
    val' <- cstringToText val
    return val'

dBusArgInfoReadSignature :: DBusArgInfo -> IO T.Text
dBusArgInfoReadSignature s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO CString
    val' <- cstringToText val
    return val'

dBusArgInfoReadAnnotations :: DBusArgInfo -> IO [DBusAnnotationInfo]
dBusArgInfoReadAnnotations s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO (Ptr (Ptr DBusAnnotationInfo))
    val' <- unpackZeroTerminatedPtrArray val
    val'' <- mapM (newBoxed DBusAnnotationInfo) val'
    return val''

-- method DBusArgInfo::ref
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DBusArgInfo", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DBusArgInfo", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Gio" "DBusArgInfo"
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_arg_info_ref" g_dbus_arg_info_ref :: 
    Ptr DBusArgInfo ->                      -- _obj : TInterface "Gio" "DBusArgInfo"
    IO (Ptr DBusArgInfo)


dBusArgInfoRef ::
    (MonadIO m) =>
    DBusArgInfo ->                          -- _obj
    m DBusArgInfo
dBusArgInfoRef _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- g_dbus_arg_info_ref _obj'
    checkUnexpectedReturnNULL "g_dbus_arg_info_ref" result
    result' <- (wrapBoxed DBusArgInfo) result
    touchManagedPtr _obj
    return result'

-- method DBusArgInfo::unref
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Gio" "DBusArgInfo", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Gio" "DBusArgInfo", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_dbus_arg_info_unref" g_dbus_arg_info_unref :: 
    Ptr DBusArgInfo ->                      -- _obj : TInterface "Gio" "DBusArgInfo"
    IO ()


dBusArgInfoUnref ::
    (MonadIO m) =>
    DBusArgInfo ->                          -- _obj
    m ()
dBusArgInfoUnref _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    g_dbus_arg_info_unref _obj'
    touchManagedPtr _obj
    return ()