{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GObject.Structs.TypeQuery
(
TypeQuery(..) ,
newZeroTypeQuery ,
noTypeQuery ,
#if defined(ENABLE_OVERLOADING)
ResolveTypeQueryMethod ,
#endif
getTypeQueryClassSize ,
setTypeQueryClassSize ,
#if defined(ENABLE_OVERLOADING)
typeQuery_classSize ,
#endif
getTypeQueryInstanceSize ,
setTypeQueryInstanceSize ,
#if defined(ENABLE_OVERLOADING)
typeQuery_instanceSize ,
#endif
getTypeQueryType ,
setTypeQueryType ,
#if defined(ENABLE_OVERLOADING)
typeQuery_type ,
#endif
clearTypeQueryTypeName ,
getTypeQueryTypeName ,
setTypeQueryTypeName ,
#if defined(ENABLE_OVERLOADING)
typeQuery_typeName ,
#endif
) 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
newtype TypeQuery = TypeQuery (ManagedPtr TypeQuery)
deriving (TypeQuery -> TypeQuery -> Bool
(TypeQuery -> TypeQuery -> Bool)
-> (TypeQuery -> TypeQuery -> Bool) -> Eq TypeQuery
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeQuery -> TypeQuery -> Bool
$c/= :: TypeQuery -> TypeQuery -> Bool
== :: TypeQuery -> TypeQuery -> Bool
$c== :: TypeQuery -> TypeQuery -> Bool
Eq)
instance WrappedPtr TypeQuery where
wrappedPtrCalloc :: IO (Ptr TypeQuery)
wrappedPtrCalloc = Int -> IO (Ptr TypeQuery)
forall a. Int -> IO (Ptr a)
callocBytes 24
wrappedPtrCopy :: TypeQuery -> IO TypeQuery
wrappedPtrCopy = \p :: TypeQuery
p -> TypeQuery -> (Ptr TypeQuery -> IO TypeQuery) -> IO TypeQuery
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeQuery
p (Int -> Ptr TypeQuery -> IO (Ptr TypeQuery)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes 24 (Ptr TypeQuery -> IO (Ptr TypeQuery))
-> (Ptr TypeQuery -> IO TypeQuery) -> Ptr TypeQuery -> IO TypeQuery
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr TypeQuery -> TypeQuery)
-> Ptr TypeQuery -> IO TypeQuery
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr TypeQuery -> TypeQuery
TypeQuery)
wrappedPtrFree :: Maybe (GDestroyNotify TypeQuery)
wrappedPtrFree = GDestroyNotify TypeQuery -> Maybe (GDestroyNotify TypeQuery)
forall a. a -> Maybe a
Just GDestroyNotify TypeQuery
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free
newZeroTypeQuery :: MonadIO m => m TypeQuery
newZeroTypeQuery :: m TypeQuery
newZeroTypeQuery = IO TypeQuery -> m TypeQuery
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TypeQuery -> m TypeQuery) -> IO TypeQuery -> m TypeQuery
forall a b. (a -> b) -> a -> b
$ IO (Ptr TypeQuery)
forall a. WrappedPtr a => IO (Ptr a)
wrappedPtrCalloc IO (Ptr TypeQuery)
-> (Ptr TypeQuery -> IO TypeQuery) -> IO TypeQuery
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr TypeQuery -> TypeQuery)
-> Ptr TypeQuery -> IO TypeQuery
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr TypeQuery -> TypeQuery
TypeQuery
instance tag ~ 'AttrSet => Constructible TypeQuery tag where
new :: (ManagedPtr TypeQuery -> TypeQuery)
-> [AttrOp TypeQuery tag] -> m TypeQuery
new _ attrs :: [AttrOp TypeQuery tag]
attrs = do
TypeQuery
o <- m TypeQuery
forall (m :: * -> *). MonadIO m => m TypeQuery
newZeroTypeQuery
TypeQuery -> [AttrOp TypeQuery 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set TypeQuery
o [AttrOp TypeQuery tag]
[AttrOp TypeQuery 'AttrSet]
attrs
TypeQuery -> m TypeQuery
forall (m :: * -> *) a. Monad m => a -> m a
return TypeQuery
o
noTypeQuery :: Maybe TypeQuery
noTypeQuery :: Maybe TypeQuery
noTypeQuery = Maybe TypeQuery
forall a. Maybe a
Nothing
getTypeQueryType :: MonadIO m => TypeQuery -> m GType
getTypeQueryType :: TypeQuery -> m GType
getTypeQueryType s :: TypeQuery
s = IO GType -> m GType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GType -> m GType) -> IO GType -> m GType
forall a b. (a -> b) -> a -> b
$ TypeQuery -> (Ptr TypeQuery -> IO GType) -> IO GType
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeQuery
s ((Ptr TypeQuery -> IO GType) -> IO GType)
-> (Ptr TypeQuery -> IO GType) -> IO GType
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TypeQuery
ptr -> do
CGType
val <- Ptr CGType -> IO CGType
forall a. Storable a => Ptr a -> IO a
peek (Ptr TypeQuery
ptr Ptr TypeQuery -> Int -> Ptr CGType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) :: IO CGType
let val' :: GType
val' = CGType -> GType
GType CGType
val
GType -> IO GType
forall (m :: * -> *) a. Monad m => a -> m a
return GType
val'
setTypeQueryType :: MonadIO m => TypeQuery -> GType -> m ()
setTypeQueryType :: TypeQuery -> GType -> m ()
setTypeQueryType s :: TypeQuery
s val :: GType
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TypeQuery -> (Ptr TypeQuery -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeQuery
s ((Ptr TypeQuery -> IO ()) -> IO ())
-> (Ptr TypeQuery -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TypeQuery
ptr -> do
let val' :: CGType
val' = GType -> CGType
gtypeToCGType GType
val
Ptr CGType -> CGType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeQuery
ptr Ptr TypeQuery -> Int -> Ptr CGType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (CGType
val' :: CGType)
#if defined(ENABLE_OVERLOADING)
data TypeQueryTypeFieldInfo
instance AttrInfo TypeQueryTypeFieldInfo where
type AttrBaseTypeConstraint TypeQueryTypeFieldInfo = (~) TypeQuery
type AttrAllowedOps TypeQueryTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TypeQueryTypeFieldInfo = (~) GType
type AttrTransferTypeConstraint TypeQueryTypeFieldInfo = (~)GType
type AttrTransferType TypeQueryTypeFieldInfo = GType
type AttrGetType TypeQueryTypeFieldInfo = GType
type AttrLabel TypeQueryTypeFieldInfo = "type"
type AttrOrigin TypeQueryTypeFieldInfo = TypeQuery
attrGet = getTypeQueryType
attrSet = setTypeQueryType
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
typeQuery_type :: AttrLabelProxy "type"
typeQuery_type = AttrLabelProxy
#endif
getTypeQueryTypeName :: MonadIO m => TypeQuery -> m (Maybe T.Text)
getTypeQueryTypeName :: TypeQuery -> m (Maybe Text)
getTypeQueryTypeName s :: TypeQuery
s = IO (Maybe Text) -> m (Maybe Text)
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
$ TypeQuery -> (Ptr TypeQuery -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeQuery
s ((Ptr TypeQuery -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr TypeQuery -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TypeQuery
ptr -> do
CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr TypeQuery
ptr Ptr TypeQuery -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) :: IO CString
Maybe Text
result <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull CString
val ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \val' :: CString
val' -> do
Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result
setTypeQueryTypeName :: MonadIO m => TypeQuery -> CString -> m ()
setTypeQueryTypeName :: TypeQuery -> CString -> m ()
setTypeQueryTypeName s :: TypeQuery
s val :: CString
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TypeQuery -> (Ptr TypeQuery -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeQuery
s ((Ptr TypeQuery -> IO ()) -> IO ())
-> (Ptr TypeQuery -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TypeQuery
ptr -> do
Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeQuery
ptr Ptr TypeQuery -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (CString
val :: CString)
clearTypeQueryTypeName :: MonadIO m => TypeQuery -> m ()
clearTypeQueryTypeName :: TypeQuery -> m ()
clearTypeQueryTypeName s :: TypeQuery
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TypeQuery -> (Ptr TypeQuery -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeQuery
s ((Ptr TypeQuery -> IO ()) -> IO ())
-> (Ptr TypeQuery -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TypeQuery
ptr -> do
Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeQuery
ptr Ptr TypeQuery -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (CString
forall a. Ptr a
FP.nullPtr :: CString)
#if defined(ENABLE_OVERLOADING)
data TypeQueryTypeNameFieldInfo
instance AttrInfo TypeQueryTypeNameFieldInfo where
type AttrBaseTypeConstraint TypeQueryTypeNameFieldInfo = (~) TypeQuery
type AttrAllowedOps TypeQueryTypeNameFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint TypeQueryTypeNameFieldInfo = (~) CString
type AttrTransferTypeConstraint TypeQueryTypeNameFieldInfo = (~)CString
type AttrTransferType TypeQueryTypeNameFieldInfo = CString
type AttrGetType TypeQueryTypeNameFieldInfo = Maybe T.Text
type AttrLabel TypeQueryTypeNameFieldInfo = "type_name"
type AttrOrigin TypeQueryTypeNameFieldInfo = TypeQuery
attrGet = getTypeQueryTypeName
attrSet = setTypeQueryTypeName
attrConstruct = undefined
attrClear = clearTypeQueryTypeName
attrTransfer _ v = do
return v
typeQuery_typeName :: AttrLabelProxy "typeName"
typeQuery_typeName = AttrLabelProxy
#endif
getTypeQueryClassSize :: MonadIO m => TypeQuery -> m Word32
getTypeQueryClassSize :: TypeQuery -> m Word32
getTypeQueryClassSize s :: TypeQuery
s = 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
$ TypeQuery -> (Ptr TypeQuery -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeQuery
s ((Ptr TypeQuery -> IO Word32) -> IO Word32)
-> (Ptr TypeQuery -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TypeQuery
ptr -> do
Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TypeQuery
ptr Ptr TypeQuery -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setTypeQueryClassSize :: MonadIO m => TypeQuery -> Word32 -> m ()
setTypeQueryClassSize :: TypeQuery -> Word32 -> m ()
setTypeQueryClassSize s :: TypeQuery
s val :: Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TypeQuery -> (Ptr TypeQuery -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeQuery
s ((Ptr TypeQuery -> IO ()) -> IO ())
-> (Ptr TypeQuery -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TypeQuery
ptr -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeQuery
ptr Ptr TypeQuery -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data TypeQueryClassSizeFieldInfo
instance AttrInfo TypeQueryClassSizeFieldInfo where
type AttrBaseTypeConstraint TypeQueryClassSizeFieldInfo = (~) TypeQuery
type AttrAllowedOps TypeQueryClassSizeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TypeQueryClassSizeFieldInfo = (~) Word32
type AttrTransferTypeConstraint TypeQueryClassSizeFieldInfo = (~)Word32
type AttrTransferType TypeQueryClassSizeFieldInfo = Word32
type AttrGetType TypeQueryClassSizeFieldInfo = Word32
type AttrLabel TypeQueryClassSizeFieldInfo = "class_size"
type AttrOrigin TypeQueryClassSizeFieldInfo = TypeQuery
attrGet = getTypeQueryClassSize
attrSet = setTypeQueryClassSize
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
typeQuery_classSize :: AttrLabelProxy "classSize"
typeQuery_classSize = AttrLabelProxy
#endif
getTypeQueryInstanceSize :: MonadIO m => TypeQuery -> m Word32
getTypeQueryInstanceSize :: TypeQuery -> m Word32
getTypeQueryInstanceSize s :: TypeQuery
s = 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
$ TypeQuery -> (Ptr TypeQuery -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeQuery
s ((Ptr TypeQuery -> IO Word32) -> IO Word32)
-> (Ptr TypeQuery -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TypeQuery
ptr -> do
Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TypeQuery
ptr Ptr TypeQuery -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setTypeQueryInstanceSize :: MonadIO m => TypeQuery -> Word32 -> m ()
setTypeQueryInstanceSize :: TypeQuery -> Word32 -> m ()
setTypeQueryInstanceSize s :: TypeQuery
s val :: Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TypeQuery -> (Ptr TypeQuery -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeQuery
s ((Ptr TypeQuery -> IO ()) -> IO ())
-> (Ptr TypeQuery -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TypeQuery
ptr -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeQuery
ptr Ptr TypeQuery -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data TypeQueryInstanceSizeFieldInfo
instance AttrInfo TypeQueryInstanceSizeFieldInfo where
type AttrBaseTypeConstraint TypeQueryInstanceSizeFieldInfo = (~) TypeQuery
type AttrAllowedOps TypeQueryInstanceSizeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TypeQueryInstanceSizeFieldInfo = (~) Word32
type AttrTransferTypeConstraint TypeQueryInstanceSizeFieldInfo = (~)Word32
type AttrTransferType TypeQueryInstanceSizeFieldInfo = Word32
type AttrGetType TypeQueryInstanceSizeFieldInfo = Word32
type AttrLabel TypeQueryInstanceSizeFieldInfo = "instance_size"
type AttrOrigin TypeQueryInstanceSizeFieldInfo = TypeQuery
attrGet = getTypeQueryInstanceSize
attrSet = setTypeQueryInstanceSize
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
typeQuery_instanceSize :: AttrLabelProxy "instanceSize"
typeQuery_instanceSize = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TypeQuery
type instance O.AttributeList TypeQuery = TypeQueryAttributeList
type TypeQueryAttributeList = ('[ '("type", TypeQueryTypeFieldInfo), '("typeName", TypeQueryTypeNameFieldInfo), '("classSize", TypeQueryClassSizeFieldInfo), '("instanceSize", TypeQueryInstanceSizeFieldInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveTypeQueryMethod (t :: Symbol) (o :: *) :: * where
ResolveTypeQueryMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveTypeQueryMethod t TypeQuery, O.MethodInfo info TypeQuery p) => OL.IsLabel t (TypeQuery -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif