{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Structs.DBusArgInfo
(
DBusArgInfo(..) ,
newZeroDBusArgInfo ,
#if defined(ENABLE_OVERLOADING)
ResolveDBusArgInfoMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DBusArgInfoRefMethodInfo ,
#endif
dBusArgInfoRef ,
#if defined(ENABLE_OVERLOADING)
DBusArgInfoUnrefMethodInfo ,
#endif
dBusArgInfoUnref ,
clearDBusArgInfoAnnotations ,
#if defined(ENABLE_OVERLOADING)
dBusArgInfo_annotations ,
#endif
getDBusArgInfoAnnotations ,
setDBusArgInfoAnnotations ,
clearDBusArgInfoName ,
#if defined(ENABLE_OVERLOADING)
dBusArgInfo_name ,
#endif
getDBusArgInfoName ,
setDBusArgInfoName ,
#if defined(ENABLE_OVERLOADING)
dBusArgInfo_refCount ,
#endif
getDBusArgInfoRefCount ,
setDBusArgInfoRefCount ,
clearDBusArgInfoSignature ,
#if defined(ENABLE_OVERLOADING)
dBusArgInfo_signature ,
#endif
getDBusArgInfoSignature ,
setDBusArgInfoSignature ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import {-# SOURCE #-} qualified GI.Gio.Structs.DBusAnnotationInfo as Gio.DBusAnnotationInfo
#else
import {-# SOURCE #-} qualified GI.Gio.Structs.DBusAnnotationInfo as Gio.DBusAnnotationInfo
#endif
newtype DBusArgInfo = DBusArgInfo (SP.ManagedPtr DBusArgInfo)
deriving (DBusArgInfo -> DBusArgInfo -> Bool
(DBusArgInfo -> DBusArgInfo -> Bool)
-> (DBusArgInfo -> DBusArgInfo -> Bool) -> Eq DBusArgInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DBusArgInfo -> DBusArgInfo -> Bool
== :: DBusArgInfo -> DBusArgInfo -> Bool
$c/= :: DBusArgInfo -> DBusArgInfo -> Bool
/= :: DBusArgInfo -> DBusArgInfo -> Bool
Eq)
instance SP.ManagedPtrNewtype DBusArgInfo where
toManagedPtr :: DBusArgInfo -> ManagedPtr DBusArgInfo
toManagedPtr (DBusArgInfo ManagedPtr DBusArgInfo
p) = ManagedPtr DBusArgInfo
p
foreign import ccall "g_dbus_arg_info_get_type" c_g_dbus_arg_info_get_type ::
IO GType
type instance O.ParentTypes DBusArgInfo = '[]
instance O.HasParentTypes DBusArgInfo
instance B.Types.TypedObject DBusArgInfo where
glibType :: IO GType
glibType = IO GType
c_g_dbus_arg_info_get_type
instance B.Types.GBoxed DBusArgInfo
instance B.GValue.IsGValue (Maybe DBusArgInfo) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_dbus_arg_info_get_type
gvalueSet_ :: Ptr GValue -> Maybe DBusArgInfo -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DBusArgInfo
P.Nothing = Ptr GValue -> Ptr DBusArgInfo -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr DBusArgInfo
forall a. Ptr a
FP.nullPtr :: FP.Ptr DBusArgInfo)
gvalueSet_ Ptr GValue
gv (P.Just DBusArgInfo
obj) = DBusArgInfo -> (Ptr DBusArgInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DBusArgInfo
obj (Ptr GValue -> Ptr DBusArgInfo -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe DBusArgInfo)
gvalueGet_ Ptr GValue
gv = do
ptr <- Ptr GValue -> IO (Ptr DBusArgInfo)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr DBusArgInfo)
if ptr /= FP.nullPtr
then P.Just <$> B.ManagedPtr.newBoxed DBusArgInfo ptr
else return P.Nothing
newZeroDBusArgInfo :: MonadIO m => m DBusArgInfo
newZeroDBusArgInfo :: forall (m :: * -> *). MonadIO m => m DBusArgInfo
newZeroDBusArgInfo = IO DBusArgInfo -> m DBusArgInfo
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusArgInfo -> m DBusArgInfo)
-> IO DBusArgInfo -> m DBusArgInfo
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr DBusArgInfo)
forall a. GBoxed a => Int -> IO (Ptr a)
callocBoxedBytes Int
32 IO (Ptr DBusArgInfo)
-> (Ptr DBusArgInfo -> IO DBusArgInfo) -> IO DBusArgInfo
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr DBusArgInfo -> DBusArgInfo)
-> Ptr DBusArgInfo -> IO DBusArgInfo
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr DBusArgInfo -> DBusArgInfo
DBusArgInfo
instance tag ~ 'AttrSet => Constructible DBusArgInfo tag where
new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr DBusArgInfo -> DBusArgInfo)
-> [AttrOp DBusArgInfo tag] -> m DBusArgInfo
new ManagedPtr DBusArgInfo -> DBusArgInfo
_ [AttrOp DBusArgInfo tag]
attrs = do
o <- m DBusArgInfo
forall (m :: * -> *). MonadIO m => m DBusArgInfo
newZeroDBusArgInfo
GI.Attributes.set o attrs
return o
getDBusArgInfoRefCount :: MonadIO m => DBusArgInfo -> m Int32
getDBusArgInfoRefCount :: forall (m :: * -> *). MonadIO m => DBusArgInfo -> m Int32
getDBusArgInfoRefCount DBusArgInfo
s = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ DBusArgInfo -> (Ptr DBusArgInfo -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusArgInfo
s ((Ptr DBusArgInfo -> IO Int32) -> IO Int32)
-> (Ptr DBusArgInfo -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr DBusArgInfo
ptr -> do
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr DBusArgInfo
ptr Ptr DBusArgInfo -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO Int32
return val
setDBusArgInfoRefCount :: MonadIO m => DBusArgInfo -> Int32 -> m ()
setDBusArgInfoRefCount :: forall (m :: * -> *). MonadIO m => DBusArgInfo -> Int32 -> m ()
setDBusArgInfoRefCount DBusArgInfo
s Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DBusArgInfo -> (Ptr DBusArgInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusArgInfo
s ((Ptr DBusArgInfo -> IO ()) -> IO ())
-> (Ptr DBusArgInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr DBusArgInfo
ptr -> do
Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DBusArgInfo
ptr Ptr DBusArgInfo -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Int32
val :: Int32)
#if defined(ENABLE_OVERLOADING)
data DBusArgInfoRefCountFieldInfo
instance AttrInfo DBusArgInfoRefCountFieldInfo where
type AttrBaseTypeConstraint DBusArgInfoRefCountFieldInfo = (~) DBusArgInfo
type AttrAllowedOps DBusArgInfoRefCountFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint DBusArgInfoRefCountFieldInfo = (~) Int32
type AttrTransferTypeConstraint DBusArgInfoRefCountFieldInfo = (~)Int32
type AttrTransferType DBusArgInfoRefCountFieldInfo = Int32
type AttrGetType DBusArgInfoRefCountFieldInfo = Int32
type AttrLabel DBusArgInfoRefCountFieldInfo = "ref_count"
type AttrOrigin DBusArgInfoRefCountFieldInfo = DBusArgInfo
attrGet :: forall o.
AttrBaseTypeConstraint DBusArgInfoRefCountFieldInfo o =>
o -> IO (AttrGetType DBusArgInfoRefCountFieldInfo)
attrGet = o -> IO (AttrGetType DBusArgInfoRefCountFieldInfo)
DBusArgInfo -> IO Int32
forall (m :: * -> *). MonadIO m => DBusArgInfo -> m Int32
getDBusArgInfoRefCount
attrSet :: forall o b.
(AttrBaseTypeConstraint DBusArgInfoRefCountFieldInfo o,
AttrSetTypeConstraint DBusArgInfoRefCountFieldInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
DBusArgInfo -> Int32 -> IO ()
forall (m :: * -> *). MonadIO m => DBusArgInfo -> Int32 -> m ()
setDBusArgInfoRefCount
attrConstruct :: forall o b.
(AttrBaseTypeConstraint DBusArgInfoRefCountFieldInfo o,
AttrSetTypeConstraint DBusArgInfoRefCountFieldInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
forall a. HasCallStack => a
undefined
attrClear :: forall o.
AttrBaseTypeConstraint DBusArgInfoRefCountFieldInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint DBusArgInfoRefCountFieldInfo o,
AttrTransferTypeConstraint DBusArgInfoRefCountFieldInfo b) =>
Proxy o -> b -> IO (AttrTransferType DBusArgInfoRefCountFieldInfo)
attrTransfer Proxy o
_ b
v = do
b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
v
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Structs.DBusArgInfo.refCount"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Structs-DBusArgInfo.html#g:attr:refCount"
})
dBusArgInfo_refCount :: AttrLabelProxy "refCount"
dBusArgInfo_refCount :: AttrLabelProxy "refCount"
dBusArgInfo_refCount = AttrLabelProxy "refCount"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
#endif
getDBusArgInfoName :: MonadIO m => DBusArgInfo -> m (Maybe T.Text)
getDBusArgInfoName :: forall (m :: * -> *). MonadIO m => DBusArgInfo -> m (Maybe Text)
getDBusArgInfoName DBusArgInfo
s = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ DBusArgInfo
-> (Ptr DBusArgInfo -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusArgInfo
s ((Ptr DBusArgInfo -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr DBusArgInfo -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr DBusArgInfo
ptr -> do
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr DBusArgInfo
ptr Ptr DBusArgInfo -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO CString
result <- SP.convertIfNonNull val $ \CString
val' -> do
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
return val''
return result
setDBusArgInfoName :: MonadIO m => DBusArgInfo -> CString -> m ()
setDBusArgInfoName :: forall (m :: * -> *). MonadIO m => DBusArgInfo -> CString -> m ()
setDBusArgInfoName DBusArgInfo
s CString
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DBusArgInfo -> (Ptr DBusArgInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusArgInfo
s ((Ptr DBusArgInfo -> IO ()) -> IO ())
-> (Ptr DBusArgInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr DBusArgInfo
ptr -> do
Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DBusArgInfo
ptr Ptr DBusArgInfo -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (CString
val :: CString)
clearDBusArgInfoName :: MonadIO m => DBusArgInfo -> m ()
clearDBusArgInfoName :: forall (m :: * -> *). MonadIO m => DBusArgInfo -> m ()
clearDBusArgInfoName DBusArgInfo
s = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DBusArgInfo -> (Ptr DBusArgInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusArgInfo
s ((Ptr DBusArgInfo -> IO ()) -> IO ())
-> (Ptr DBusArgInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr DBusArgInfo
ptr -> do
Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DBusArgInfo
ptr Ptr DBusArgInfo -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (CString
forall a. Ptr a
FP.nullPtr :: CString)
#if defined(ENABLE_OVERLOADING)
data DBusArgInfoNameFieldInfo
instance AttrInfo DBusArgInfoNameFieldInfo where
type AttrBaseTypeConstraint DBusArgInfoNameFieldInfo = (~) DBusArgInfo
type AttrAllowedOps DBusArgInfoNameFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint DBusArgInfoNameFieldInfo = (~) CString
type AttrTransferTypeConstraint DBusArgInfoNameFieldInfo = (~)CString
type AttrTransferType DBusArgInfoNameFieldInfo = CString
type AttrGetType DBusArgInfoNameFieldInfo = Maybe T.Text
type AttrLabel DBusArgInfoNameFieldInfo = "name"
type AttrOrigin DBusArgInfoNameFieldInfo = DBusArgInfo
attrGet :: forall o.
AttrBaseTypeConstraint DBusArgInfoNameFieldInfo o =>
o -> IO (AttrGetType DBusArgInfoNameFieldInfo)
attrGet = o -> IO (AttrGetType DBusArgInfoNameFieldInfo)
DBusArgInfo -> IO (Maybe Text)
forall (m :: * -> *). MonadIO m => DBusArgInfo -> m (Maybe Text)
getDBusArgInfoName
attrSet :: forall o b.
(AttrBaseTypeConstraint DBusArgInfoNameFieldInfo o,
AttrSetTypeConstraint DBusArgInfoNameFieldInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
DBusArgInfo -> CString -> IO ()
forall (m :: * -> *). MonadIO m => DBusArgInfo -> CString -> m ()
setDBusArgInfoName
attrConstruct :: forall o b.
(AttrBaseTypeConstraint DBusArgInfoNameFieldInfo o,
AttrSetTypeConstraint DBusArgInfoNameFieldInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
forall a. HasCallStack => a
undefined
attrClear :: forall o.
AttrBaseTypeConstraint DBusArgInfoNameFieldInfo o =>
o -> IO ()
attrClear = o -> IO ()
DBusArgInfo -> IO ()
forall (m :: * -> *). MonadIO m => DBusArgInfo -> m ()
clearDBusArgInfoName
attrTransfer :: forall o b.
(AttrBaseTypeConstraint DBusArgInfoNameFieldInfo o,
AttrTransferTypeConstraint DBusArgInfoNameFieldInfo b) =>
Proxy o -> b -> IO (AttrTransferType DBusArgInfoNameFieldInfo)
attrTransfer Proxy o
_ b
v = do
b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
v
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Structs.DBusArgInfo.name"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Structs-DBusArgInfo.html#g:attr:name"
})
dBusArgInfo_name :: AttrLabelProxy "name"
dBusArgInfo_name :: AttrLabelProxy "name"
dBusArgInfo_name = AttrLabelProxy "name"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
#endif
getDBusArgInfoSignature :: MonadIO m => DBusArgInfo -> m (Maybe T.Text)
getDBusArgInfoSignature :: forall (m :: * -> *). MonadIO m => DBusArgInfo -> m (Maybe Text)
getDBusArgInfoSignature DBusArgInfo
s = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ DBusArgInfo
-> (Ptr DBusArgInfo -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusArgInfo
s ((Ptr DBusArgInfo -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr DBusArgInfo -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr DBusArgInfo
ptr -> do
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr DBusArgInfo
ptr Ptr DBusArgInfo -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO CString
result <- SP.convertIfNonNull val $ \CString
val' -> do
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
return val''
return result
setDBusArgInfoSignature :: MonadIO m => DBusArgInfo -> CString -> m ()
setDBusArgInfoSignature :: forall (m :: * -> *). MonadIO m => DBusArgInfo -> CString -> m ()
setDBusArgInfoSignature DBusArgInfo
s CString
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DBusArgInfo -> (Ptr DBusArgInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusArgInfo
s ((Ptr DBusArgInfo -> IO ()) -> IO ())
-> (Ptr DBusArgInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr DBusArgInfo
ptr -> do
Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DBusArgInfo
ptr Ptr DBusArgInfo -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (CString
val :: CString)
clearDBusArgInfoSignature :: MonadIO m => DBusArgInfo -> m ()
clearDBusArgInfoSignature :: forall (m :: * -> *). MonadIO m => DBusArgInfo -> m ()
clearDBusArgInfoSignature DBusArgInfo
s = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DBusArgInfo -> (Ptr DBusArgInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusArgInfo
s ((Ptr DBusArgInfo -> IO ()) -> IO ())
-> (Ptr DBusArgInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr DBusArgInfo
ptr -> do
Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DBusArgInfo
ptr Ptr DBusArgInfo -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (CString
forall a. Ptr a
FP.nullPtr :: CString)
#if defined(ENABLE_OVERLOADING)
data DBusArgInfoSignatureFieldInfo
instance AttrInfo DBusArgInfoSignatureFieldInfo where
type AttrBaseTypeConstraint DBusArgInfoSignatureFieldInfo = (~) DBusArgInfo
type AttrAllowedOps DBusArgInfoSignatureFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint DBusArgInfoSignatureFieldInfo = (~) CString
type AttrTransferTypeConstraint DBusArgInfoSignatureFieldInfo = (~)CString
type AttrTransferType DBusArgInfoSignatureFieldInfo = CString
type AttrGetType DBusArgInfoSignatureFieldInfo = Maybe T.Text
type AttrLabel DBusArgInfoSignatureFieldInfo = "signature"
type AttrOrigin DBusArgInfoSignatureFieldInfo = DBusArgInfo
attrGet :: forall o.
AttrBaseTypeConstraint DBusArgInfoSignatureFieldInfo o =>
o -> IO (AttrGetType DBusArgInfoSignatureFieldInfo)
attrGet = o -> IO (AttrGetType DBusArgInfoSignatureFieldInfo)
DBusArgInfo -> IO (Maybe Text)
forall (m :: * -> *). MonadIO m => DBusArgInfo -> m (Maybe Text)
getDBusArgInfoSignature
attrSet :: forall o b.
(AttrBaseTypeConstraint DBusArgInfoSignatureFieldInfo o,
AttrSetTypeConstraint DBusArgInfoSignatureFieldInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
DBusArgInfo -> CString -> IO ()
forall (m :: * -> *). MonadIO m => DBusArgInfo -> CString -> m ()
setDBusArgInfoSignature
attrConstruct :: forall o b.
(AttrBaseTypeConstraint DBusArgInfoSignatureFieldInfo o,
AttrSetTypeConstraint DBusArgInfoSignatureFieldInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
forall a. HasCallStack => a
undefined
attrClear :: forall o.
AttrBaseTypeConstraint DBusArgInfoSignatureFieldInfo o =>
o -> IO ()
attrClear = o -> IO ()
DBusArgInfo -> IO ()
forall (m :: * -> *). MonadIO m => DBusArgInfo -> m ()
clearDBusArgInfoSignature
attrTransfer :: forall o b.
(AttrBaseTypeConstraint DBusArgInfoSignatureFieldInfo o,
AttrTransferTypeConstraint DBusArgInfoSignatureFieldInfo b) =>
Proxy o -> b -> IO (AttrTransferType DBusArgInfoSignatureFieldInfo)
attrTransfer Proxy o
_ b
v = do
b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
v
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Structs.DBusArgInfo.signature"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Structs-DBusArgInfo.html#g:attr:signature"
})
dBusArgInfo_signature :: AttrLabelProxy "signature"
dBusArgInfo_signature :: AttrLabelProxy "signature"
dBusArgInfo_signature = AttrLabelProxy "signature"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
#endif
getDBusArgInfoAnnotations :: MonadIO m => DBusArgInfo -> m (Maybe [Gio.DBusAnnotationInfo.DBusAnnotationInfo])
getDBusArgInfoAnnotations :: forall (m :: * -> *).
MonadIO m =>
DBusArgInfo -> m (Maybe [DBusAnnotationInfo])
getDBusArgInfoAnnotations DBusArgInfo
s = IO (Maybe [DBusAnnotationInfo]) -> m (Maybe [DBusAnnotationInfo])
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe [DBusAnnotationInfo]) -> m (Maybe [DBusAnnotationInfo]))
-> IO (Maybe [DBusAnnotationInfo])
-> m (Maybe [DBusAnnotationInfo])
forall a b. (a -> b) -> a -> b
$ DBusArgInfo
-> (Ptr DBusArgInfo -> IO (Maybe [DBusAnnotationInfo]))
-> IO (Maybe [DBusAnnotationInfo])
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusArgInfo
s ((Ptr DBusArgInfo -> IO (Maybe [DBusAnnotationInfo]))
-> IO (Maybe [DBusAnnotationInfo]))
-> (Ptr DBusArgInfo -> IO (Maybe [DBusAnnotationInfo]))
-> IO (Maybe [DBusAnnotationInfo])
forall a b. (a -> b) -> a -> b
$ \Ptr DBusArgInfo
ptr -> do
val <- Ptr (Ptr (Ptr DBusAnnotationInfo))
-> IO (Ptr (Ptr DBusAnnotationInfo))
forall a. Storable a => Ptr a -> IO a
peek (Ptr DBusArgInfo
ptr Ptr DBusArgInfo -> Int -> Ptr (Ptr (Ptr DBusAnnotationInfo))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) :: IO (Ptr (Ptr Gio.DBusAnnotationInfo.DBusAnnotationInfo))
result <- SP.convertIfNonNull val $ \Ptr (Ptr DBusAnnotationInfo)
val' -> do
val'' <- Ptr (Ptr DBusAnnotationInfo) -> IO [Ptr DBusAnnotationInfo]
forall a. Ptr (Ptr a) -> IO [Ptr a]
unpackZeroTerminatedPtrArray Ptr (Ptr DBusAnnotationInfo)
val'
val''' <- mapM (newBoxed Gio.DBusAnnotationInfo.DBusAnnotationInfo) val''
return val'''
return result
setDBusArgInfoAnnotations :: MonadIO m => DBusArgInfo -> Ptr (Ptr Gio.DBusAnnotationInfo.DBusAnnotationInfo) -> m ()
setDBusArgInfoAnnotations :: forall (m :: * -> *).
MonadIO m =>
DBusArgInfo -> Ptr (Ptr DBusAnnotationInfo) -> m ()
setDBusArgInfoAnnotations DBusArgInfo
s Ptr (Ptr DBusAnnotationInfo)
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DBusArgInfo -> (Ptr DBusArgInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusArgInfo
s ((Ptr DBusArgInfo -> IO ()) -> IO ())
-> (Ptr DBusArgInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr DBusArgInfo
ptr -> do
Ptr (Ptr (Ptr DBusAnnotationInfo))
-> Ptr (Ptr DBusAnnotationInfo) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DBusArgInfo
ptr Ptr DBusArgInfo -> Int -> Ptr (Ptr (Ptr DBusAnnotationInfo))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (Ptr (Ptr DBusAnnotationInfo)
val :: Ptr (Ptr Gio.DBusAnnotationInfo.DBusAnnotationInfo))
clearDBusArgInfoAnnotations :: MonadIO m => DBusArgInfo -> m ()
clearDBusArgInfoAnnotations :: forall (m :: * -> *). MonadIO m => DBusArgInfo -> m ()
clearDBusArgInfoAnnotations DBusArgInfo
s = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DBusArgInfo -> (Ptr DBusArgInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusArgInfo
s ((Ptr DBusArgInfo -> IO ()) -> IO ())
-> (Ptr DBusArgInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr DBusArgInfo
ptr -> do
Ptr (Ptr (Ptr DBusAnnotationInfo))
-> Ptr (Ptr DBusAnnotationInfo) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DBusArgInfo
ptr Ptr DBusArgInfo -> Int -> Ptr (Ptr (Ptr DBusAnnotationInfo))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (Ptr (Ptr DBusAnnotationInfo)
forall a. Ptr a
FP.nullPtr :: Ptr (Ptr Gio.DBusAnnotationInfo.DBusAnnotationInfo))
#if defined(ENABLE_OVERLOADING)
data DBusArgInfoAnnotationsFieldInfo
instance AttrInfo DBusArgInfoAnnotationsFieldInfo where
type AttrBaseTypeConstraint DBusArgInfoAnnotationsFieldInfo = (~) DBusArgInfo
type AttrAllowedOps DBusArgInfoAnnotationsFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint DBusArgInfoAnnotationsFieldInfo = (~) (Ptr (Ptr Gio.DBusAnnotationInfo.DBusAnnotationInfo))
type AttrTransferTypeConstraint DBusArgInfoAnnotationsFieldInfo = (~)(Ptr (Ptr Gio.DBusAnnotationInfo.DBusAnnotationInfo))
type AttrTransferType DBusArgInfoAnnotationsFieldInfo = (Ptr (Ptr Gio.DBusAnnotationInfo.DBusAnnotationInfo))
type AttrGetType DBusArgInfoAnnotationsFieldInfo = Maybe [Gio.DBusAnnotationInfo.DBusAnnotationInfo]
type AttrLabel DBusArgInfoAnnotationsFieldInfo = "annotations"
type AttrOrigin DBusArgInfoAnnotationsFieldInfo = DBusArgInfo
attrGet :: forall o.
AttrBaseTypeConstraint DBusArgInfoAnnotationsFieldInfo o =>
o -> IO (AttrGetType DBusArgInfoAnnotationsFieldInfo)
attrGet = o -> IO (AttrGetType DBusArgInfoAnnotationsFieldInfo)
DBusArgInfo -> IO (Maybe [DBusAnnotationInfo])
forall (m :: * -> *).
MonadIO m =>
DBusArgInfo -> m (Maybe [DBusAnnotationInfo])
getDBusArgInfoAnnotations
attrSet :: forall o b.
(AttrBaseTypeConstraint DBusArgInfoAnnotationsFieldInfo o,
AttrSetTypeConstraint DBusArgInfoAnnotationsFieldInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
DBusArgInfo -> Ptr (Ptr DBusAnnotationInfo) -> IO ()
forall (m :: * -> *).
MonadIO m =>
DBusArgInfo -> Ptr (Ptr DBusAnnotationInfo) -> m ()
setDBusArgInfoAnnotations
attrConstruct :: forall o b.
(AttrBaseTypeConstraint DBusArgInfoAnnotationsFieldInfo o,
AttrSetTypeConstraint DBusArgInfoAnnotationsFieldInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
forall a. HasCallStack => a
undefined
attrClear :: forall o.
AttrBaseTypeConstraint DBusArgInfoAnnotationsFieldInfo o =>
o -> IO ()
attrClear = o -> IO ()
DBusArgInfo -> IO ()
forall (m :: * -> *). MonadIO m => DBusArgInfo -> m ()
clearDBusArgInfoAnnotations
attrTransfer :: forall o b.
(AttrBaseTypeConstraint DBusArgInfoAnnotationsFieldInfo o,
AttrTransferTypeConstraint DBusArgInfoAnnotationsFieldInfo b) =>
Proxy o
-> b -> IO (AttrTransferType DBusArgInfoAnnotationsFieldInfo)
attrTransfer Proxy o
_ b
v = do
b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
v
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Structs.DBusArgInfo.annotations"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Structs-DBusArgInfo.html#g:attr:annotations"
})
dBusArgInfo_annotations :: AttrLabelProxy "annotations"
dBusArgInfo_annotations :: AttrLabelProxy "annotations"
dBusArgInfo_annotations = AttrLabelProxy "annotations"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DBusArgInfo
type instance O.AttributeList DBusArgInfo = DBusArgInfoAttributeList
type DBusArgInfoAttributeList = ('[ '("refCount", DBusArgInfoRefCountFieldInfo), '("name", DBusArgInfoNameFieldInfo), '("signature", DBusArgInfoSignatureFieldInfo), '("annotations", DBusArgInfoAnnotationsFieldInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "g_dbus_arg_info_ref" g_dbus_arg_info_ref ::
Ptr DBusArgInfo ->
IO (Ptr DBusArgInfo)
dBusArgInfoRef ::
(B.CallStack.HasCallStack, MonadIO m) =>
DBusArgInfo
-> m DBusArgInfo
dBusArgInfoRef :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
DBusArgInfo -> m DBusArgInfo
dBusArgInfoRef DBusArgInfo
info = IO DBusArgInfo -> m DBusArgInfo
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DBusArgInfo -> m DBusArgInfo)
-> IO DBusArgInfo -> m DBusArgInfo
forall a b. (a -> b) -> a -> b
$ do
info' <- DBusArgInfo -> IO (Ptr DBusArgInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DBusArgInfo
info
result <- g_dbus_arg_info_ref info'
checkUnexpectedReturnNULL "dBusArgInfoRef" result
result' <- (wrapBoxed DBusArgInfo) result
touchManagedPtr info
return result'
#if defined(ENABLE_OVERLOADING)
data DBusArgInfoRefMethodInfo
instance (signature ~ (m DBusArgInfo), MonadIO m) => O.OverloadedMethod DBusArgInfoRefMethodInfo DBusArgInfo signature where
overloadedMethod :: DBusArgInfo -> signature
overloadedMethod = DBusArgInfo -> signature
DBusArgInfo -> m DBusArgInfo
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
DBusArgInfo -> m DBusArgInfo
dBusArgInfoRef
instance O.OverloadedMethodInfo DBusArgInfoRefMethodInfo DBusArgInfo where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Structs.DBusArgInfo.dBusArgInfoRef",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Structs-DBusArgInfo.html#v:dBusArgInfoRef"
})
#endif
foreign import ccall "g_dbus_arg_info_unref" g_dbus_arg_info_unref ::
Ptr DBusArgInfo ->
IO ()
dBusArgInfoUnref ::
(B.CallStack.HasCallStack, MonadIO m) =>
DBusArgInfo
-> m ()
dBusArgInfoUnref :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
DBusArgInfo -> m ()
dBusArgInfoUnref DBusArgInfo
info = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
info' <- DBusArgInfo -> IO (Ptr DBusArgInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DBusArgInfo
info
g_dbus_arg_info_unref info'
touchManagedPtr info
return ()
#if defined(ENABLE_OVERLOADING)
data DBusArgInfoUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod DBusArgInfoUnrefMethodInfo DBusArgInfo signature where
overloadedMethod :: DBusArgInfo -> signature
overloadedMethod = DBusArgInfo -> signature
DBusArgInfo -> m ()
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
DBusArgInfo -> m ()
dBusArgInfoUnref
instance O.OverloadedMethodInfo DBusArgInfoUnrefMethodInfo DBusArgInfo where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Structs.DBusArgInfo.dBusArgInfoUnref",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Structs-DBusArgInfo.html#v:dBusArgInfoUnref"
})
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveDBusArgInfoMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveDBusArgInfoMethod "ref" o = DBusArgInfoRefMethodInfo
ResolveDBusArgInfoMethod "unref" o = DBusArgInfoUnrefMethodInfo
ResolveDBusArgInfoMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveDBusArgInfoMethod t DBusArgInfo, O.OverloadedMethod info DBusArgInfo p) => OL.IsLabel t (DBusArgInfo -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel :: DBusArgInfo -> p
fromLabel = forall {k} (i :: k) o s. OverloadedMethod i o s => o -> s
forall i o s. OverloadedMethod i o s => o -> s
O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveDBusArgInfoMethod t DBusArgInfo, O.OverloadedMethod info DBusArgInfo p, R.HasField t DBusArgInfo p) => R.HasField t DBusArgInfo p where
getField :: DBusArgInfo -> p
getField = forall {k} (i :: k) o s. OverloadedMethod i o s => o -> s
forall i o s. OverloadedMethod i o s => o -> s
O.overloadedMethod @info
#endif
instance (info ~ ResolveDBusArgInfoMethod t DBusArgInfo, O.OverloadedMethodInfo info DBusArgInfo) => OL.IsLabel t (O.MethodProxy info DBusArgInfo) where
#if MIN_VERSION_base(4,10,0)
fromLabel :: MethodProxy info DBusArgInfo
fromLabel = MethodProxy info DBusArgInfo
forall info obj. MethodProxy info obj
O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif