{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.GObject.Structs.TypeValueTable.TypeValueTable' provides the functions required by the t'GI.GObject.Structs.Value.Value'
-- implementation, to serve as a container for values of a type.

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

module GI.GObject.Structs.TypeValueTable
    ( 

-- * Exported types
    TypeValueTable(..)                      ,
    newZeroTypeValueTable                   ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveTypeValueTableMethod             ,
#endif



 -- * Properties


-- ** collectFormat #attr:collectFormat#
-- | A string format describing how to collect the contents of
--   this value bit-by-bit. Each character in the format represents
--   an argument to be collected, and the characters themselves indicate
--   the type of the argument. Currently supported arguments are:
--    - @\'i\'@: Integers, passed as @collect_values[].v_int@
--    - @\'l\'@: Longs, passed as @collect_values[].v_long@
--    - @\'d\'@: Doubles, passed as @collect_values[].v_double@
--    - @\'p\'@: Pointers, passed as @collect_values[].v_pointer@
--   It should be noted that for variable argument list construction,
--   ANSI C promotes every type smaller than an integer to an int, and
--   floats to doubles. So for collection of short int or char, @\'i\'@
--   needs to be used, and for collection of floats @\'d\'@.

    clearTypeValueTableCollectFormat        ,
    getTypeValueTableCollectFormat          ,
    setTypeValueTableCollectFormat          ,
#if defined(ENABLE_OVERLOADING)
    typeValueTable_collectFormat            ,
#endif


-- ** collectValue #attr:collectValue#
-- | Function to initialize a GValue from the values
--   collected from variadic arguments

    clearTypeValueTableCollectValue         ,
    getTypeValueTableCollectValue           ,
    setTypeValueTableCollectValue           ,
#if defined(ENABLE_OVERLOADING)
    typeValueTable_collectValue             ,
#endif


-- ** lcopyFormat #attr:lcopyFormat#
-- | Format description of the arguments to collect for /@lcopyValue@/,
--   analogous to /@collectFormat@/. Usually, /@lcopyFormat@/ string consists
--   only of @\'p\'@s to provide @/lcopy_value()/@ with pointers to storage locations.

    clearTypeValueTableLcopyFormat          ,
    getTypeValueTableLcopyFormat            ,
    setTypeValueTableLcopyFormat            ,
#if defined(ENABLE_OVERLOADING)
    typeValueTable_lcopyFormat              ,
#endif


-- ** lcopyValue #attr:lcopyValue#
-- | Function to store the contents of a value into the
--   locations collected from variadic arguments

    clearTypeValueTableLcopyValue           ,
    getTypeValueTableLcopyValue             ,
    setTypeValueTableLcopyValue             ,
#if defined(ENABLE_OVERLOADING)
    typeValueTable_lcopyValue               ,
#endif


-- ** valueCopy #attr:valueCopy#
-- | Function to copy a GValue

    clearTypeValueTableValueCopy            ,
    getTypeValueTableValueCopy              ,
    setTypeValueTableValueCopy              ,
#if defined(ENABLE_OVERLOADING)
    typeValueTable_valueCopy                ,
#endif


-- ** valueFree #attr:valueFree#
-- | Function to free a GValue

    clearTypeValueTableValueFree            ,
    getTypeValueTableValueFree              ,
    setTypeValueTableValueFree              ,
#if defined(ENABLE_OVERLOADING)
    typeValueTable_valueFree                ,
#endif


-- ** valueInit #attr:valueInit#
-- | Function to initialize a GValue

    clearTypeValueTableValueInit            ,
    getTypeValueTableValueInit              ,
    setTypeValueTableValueInit              ,
#if defined(ENABLE_OVERLOADING)
    typeValueTable_valueInit                ,
#endif


-- ** valuePeekPointer #attr:valuePeekPointer#
-- | Function to peek the contents of a GValue if they fit
--   into a pointer

    clearTypeValueTableValuePeekPointer     ,
    getTypeValueTableValuePeekPointer       ,
    setTypeValueTableValuePeekPointer       ,
#if defined(ENABLE_OVERLOADING)
    typeValueTable_valuePeekPointer         ,
#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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import qualified GI.GObject.Callbacks as GObject.Callbacks

#else
import qualified GI.GObject.Callbacks as GObject.Callbacks

#endif

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

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

instance BoxedPtr TypeValueTable where
    boxedPtrCopy :: TypeValueTable -> IO TypeValueTable
boxedPtrCopy = \TypeValueTable
p -> TypeValueTable
-> (Ptr TypeValueTable -> IO TypeValueTable) -> IO TypeValueTable
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TypeValueTable
p (Int -> Ptr TypeValueTable -> IO (Ptr TypeValueTable)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
64 (Ptr TypeValueTable -> IO (Ptr TypeValueTable))
-> (Ptr TypeValueTable -> IO TypeValueTable)
-> Ptr TypeValueTable
-> IO TypeValueTable
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr TypeValueTable -> TypeValueTable)
-> Ptr TypeValueTable -> IO TypeValueTable
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr TypeValueTable -> TypeValueTable
TypeValueTable)
    boxedPtrFree :: TypeValueTable -> IO ()
boxedPtrFree = \TypeValueTable
x -> TypeValueTable -> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr TypeValueTable
x Ptr TypeValueTable -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr TypeValueTable where
    boxedPtrCalloc :: IO (Ptr TypeValueTable)
boxedPtrCalloc = Int -> IO (Ptr TypeValueTable)
forall a. Int -> IO (Ptr a)
callocBytes Int
64


-- | Construct a `TypeValueTable` struct initialized to zero.
newZeroTypeValueTable :: MonadIO m => m TypeValueTable
newZeroTypeValueTable :: forall (m :: * -> *). MonadIO m => m TypeValueTable
newZeroTypeValueTable = IO TypeValueTable -> m TypeValueTable
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TypeValueTable -> m TypeValueTable)
-> IO TypeValueTable -> m TypeValueTable
forall a b. (a -> b) -> a -> b
$ IO (Ptr TypeValueTable)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr TypeValueTable)
-> (Ptr TypeValueTable -> IO TypeValueTable) -> IO TypeValueTable
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr TypeValueTable -> TypeValueTable)
-> Ptr TypeValueTable -> IO TypeValueTable
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr TypeValueTable -> TypeValueTable
TypeValueTable

instance tag ~ 'AttrSet => Constructible TypeValueTable tag where
    new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr TypeValueTable -> TypeValueTable)
-> [AttrOp TypeValueTable tag] -> m TypeValueTable
new ManagedPtr TypeValueTable -> TypeValueTable
_ [AttrOp TypeValueTable tag]
attrs = do
        TypeValueTable
o <- m TypeValueTable
forall (m :: * -> *). MonadIO m => m TypeValueTable
newZeroTypeValueTable
        TypeValueTable -> [AttrOp TypeValueTable 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set TypeValueTable
o [AttrOp TypeValueTable tag]
[AttrOp TypeValueTable 'AttrSet]
attrs
        TypeValueTable -> m TypeValueTable
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return TypeValueTable
o


-- | Get the value of the “@value_init@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' typeValueTable #valueInit
-- @
getTypeValueTableValueInit :: MonadIO m => TypeValueTable -> m (Maybe GObject.Callbacks.TypeValueInitFunc)
getTypeValueTableValueInit :: forall (m :: * -> *).
MonadIO m =>
TypeValueTable -> m (Maybe TypeValueInitFunc)
getTypeValueTableValueInit TypeValueTable
s = IO (Maybe TypeValueInitFunc) -> m (Maybe TypeValueInitFunc)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TypeValueInitFunc) -> m (Maybe TypeValueInitFunc))
-> IO (Maybe TypeValueInitFunc) -> m (Maybe TypeValueInitFunc)
forall a b. (a -> b) -> a -> b
$ TypeValueTable
-> (Ptr TypeValueTable -> IO (Maybe TypeValueInitFunc))
-> IO (Maybe TypeValueInitFunc)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeValueTable
s ((Ptr TypeValueTable -> IO (Maybe TypeValueInitFunc))
 -> IO (Maybe TypeValueInitFunc))
-> (Ptr TypeValueTable -> IO (Maybe TypeValueInitFunc))
-> IO (Maybe TypeValueInitFunc)
forall a b. (a -> b) -> a -> b
$ \Ptr TypeValueTable
ptr -> do
    FunPtr C_TypeValueInitFunc
val <- Ptr (FunPtr C_TypeValueInitFunc) -> IO (FunPtr C_TypeValueInitFunc)
forall a. Storable a => Ptr a -> IO a
peek (Ptr TypeValueTable
ptr Ptr TypeValueTable -> Int -> Ptr (FunPtr C_TypeValueInitFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO (FunPtr GObject.Callbacks.C_TypeValueInitFunc)
    Maybe TypeValueInitFunc
result <- FunPtr C_TypeValueInitFunc
-> (FunPtr C_TypeValueInitFunc -> IO TypeValueInitFunc)
-> IO (Maybe TypeValueInitFunc)
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr C_TypeValueInitFunc
val ((FunPtr C_TypeValueInitFunc -> IO TypeValueInitFunc)
 -> IO (Maybe TypeValueInitFunc))
-> (FunPtr C_TypeValueInitFunc -> IO TypeValueInitFunc)
-> IO (Maybe TypeValueInitFunc)
forall a b. (a -> b) -> a -> b
$ \FunPtr C_TypeValueInitFunc
val' -> do
        let val'' :: TypeValueInitFunc
val'' = FunPtr C_TypeValueInitFunc -> TypeValueInitFunc
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_TypeValueInitFunc -> GValue -> m ()
GObject.Callbacks.dynamic_TypeValueInitFunc FunPtr C_TypeValueInitFunc
val'
        TypeValueInitFunc -> IO TypeValueInitFunc
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TypeValueInitFunc
val''
    Maybe TypeValueInitFunc -> IO (Maybe TypeValueInitFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TypeValueInitFunc
result

-- | Set the value of the “@value_init@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' typeValueTable [ #valueInit 'Data.GI.Base.Attributes.:=' value ]
-- @
setTypeValueTableValueInit :: MonadIO m => TypeValueTable -> FunPtr GObject.Callbacks.C_TypeValueInitFunc -> m ()
setTypeValueTableValueInit :: forall (m :: * -> *).
MonadIO m =>
TypeValueTable -> FunPtr C_TypeValueInitFunc -> m ()
setTypeValueTableValueInit TypeValueTable
s FunPtr C_TypeValueInitFunc
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
$ TypeValueTable -> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeValueTable
s ((Ptr TypeValueTable -> IO ()) -> IO ())
-> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeValueTable
ptr -> do
    Ptr (FunPtr C_TypeValueInitFunc)
-> FunPtr C_TypeValueInitFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeValueTable
ptr Ptr TypeValueTable -> Int -> Ptr (FunPtr C_TypeValueInitFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (FunPtr C_TypeValueInitFunc
val :: FunPtr GObject.Callbacks.C_TypeValueInitFunc)

-- | Set the value of the “@value_init@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #valueInit
-- @
clearTypeValueTableValueInit :: MonadIO m => TypeValueTable -> m ()
clearTypeValueTableValueInit :: forall (m :: * -> *). MonadIO m => TypeValueTable -> m ()
clearTypeValueTableValueInit TypeValueTable
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
$ TypeValueTable -> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeValueTable
s ((Ptr TypeValueTable -> IO ()) -> IO ())
-> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeValueTable
ptr -> do
    Ptr (FunPtr C_TypeValueInitFunc)
-> FunPtr C_TypeValueInitFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeValueTable
ptr Ptr TypeValueTable -> Int -> Ptr (FunPtr C_TypeValueInitFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (FunPtr C_TypeValueInitFunc
forall a. FunPtr a
FP.nullFunPtr :: FunPtr GObject.Callbacks.C_TypeValueInitFunc)

#if defined(ENABLE_OVERLOADING)
data TypeValueTableValueInitFieldInfo
instance AttrInfo TypeValueTableValueInitFieldInfo where
    type AttrBaseTypeConstraint TypeValueTableValueInitFieldInfo = (~) TypeValueTable
    type AttrAllowedOps TypeValueTableValueInitFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TypeValueTableValueInitFieldInfo = (~) (FunPtr GObject.Callbacks.C_TypeValueInitFunc)
    type AttrTransferTypeConstraint TypeValueTableValueInitFieldInfo = (~)GObject.Callbacks.TypeValueInitFunc
    type AttrTransferType TypeValueTableValueInitFieldInfo = (FunPtr GObject.Callbacks.C_TypeValueInitFunc)
    type AttrGetType TypeValueTableValueInitFieldInfo = Maybe GObject.Callbacks.TypeValueInitFunc
    type AttrLabel TypeValueTableValueInitFieldInfo = "value_init"
    type AttrOrigin TypeValueTableValueInitFieldInfo = TypeValueTable
    attrGet = getTypeValueTableValueInit
    attrSet = setTypeValueTableValueInit
    attrConstruct = undefined
    attrClear = clearTypeValueTableValueInit
    attrTransfer _ v = do
        GObject.Callbacks.mk_TypeValueInitFunc (GObject.Callbacks.wrap_TypeValueInitFunc Nothing v)
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GObject.Structs.TypeValueTable.valueInit"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.31/docs/GI-GObject-Structs-TypeValueTable.html#g:attr:valueInit"
        })

typeValueTable_valueInit :: AttrLabelProxy "valueInit"
typeValueTable_valueInit = AttrLabelProxy

#endif


-- | Get the value of the “@value_free@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' typeValueTable #valueFree
-- @
getTypeValueTableValueFree :: MonadIO m => TypeValueTable -> m (Maybe GObject.Callbacks.TypeValueFreeFunc)
getTypeValueTableValueFree :: forall (m :: * -> *).
MonadIO m =>
TypeValueTable -> m (Maybe TypeValueInitFunc)
getTypeValueTableValueFree TypeValueTable
s = IO (Maybe TypeValueInitFunc) -> m (Maybe TypeValueInitFunc)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TypeValueInitFunc) -> m (Maybe TypeValueInitFunc))
-> IO (Maybe TypeValueInitFunc) -> m (Maybe TypeValueInitFunc)
forall a b. (a -> b) -> a -> b
$ TypeValueTable
-> (Ptr TypeValueTable -> IO (Maybe TypeValueInitFunc))
-> IO (Maybe TypeValueInitFunc)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeValueTable
s ((Ptr TypeValueTable -> IO (Maybe TypeValueInitFunc))
 -> IO (Maybe TypeValueInitFunc))
-> (Ptr TypeValueTable -> IO (Maybe TypeValueInitFunc))
-> IO (Maybe TypeValueInitFunc)
forall a b. (a -> b) -> a -> b
$ \Ptr TypeValueTable
ptr -> do
    FunPtr C_TypeValueInitFunc
val <- Ptr (FunPtr C_TypeValueInitFunc) -> IO (FunPtr C_TypeValueInitFunc)
forall a. Storable a => Ptr a -> IO a
peek (Ptr TypeValueTable
ptr Ptr TypeValueTable -> Int -> Ptr (FunPtr C_TypeValueInitFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO (FunPtr GObject.Callbacks.C_TypeValueFreeFunc)
    Maybe TypeValueInitFunc
result <- FunPtr C_TypeValueInitFunc
-> (FunPtr C_TypeValueInitFunc -> IO TypeValueInitFunc)
-> IO (Maybe TypeValueInitFunc)
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr C_TypeValueInitFunc
val ((FunPtr C_TypeValueInitFunc -> IO TypeValueInitFunc)
 -> IO (Maybe TypeValueInitFunc))
-> (FunPtr C_TypeValueInitFunc -> IO TypeValueInitFunc)
-> IO (Maybe TypeValueInitFunc)
forall a b. (a -> b) -> a -> b
$ \FunPtr C_TypeValueInitFunc
val' -> do
        let val'' :: TypeValueInitFunc
val'' = FunPtr C_TypeValueInitFunc -> TypeValueInitFunc
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_TypeValueInitFunc -> GValue -> m ()
GObject.Callbacks.dynamic_TypeValueFreeFunc FunPtr C_TypeValueInitFunc
val'
        TypeValueInitFunc -> IO TypeValueInitFunc
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TypeValueInitFunc
val''
    Maybe TypeValueInitFunc -> IO (Maybe TypeValueInitFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TypeValueInitFunc
result

-- | Set the value of the “@value_free@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' typeValueTable [ #valueFree 'Data.GI.Base.Attributes.:=' value ]
-- @
setTypeValueTableValueFree :: MonadIO m => TypeValueTable -> FunPtr GObject.Callbacks.C_TypeValueFreeFunc -> m ()
setTypeValueTableValueFree :: forall (m :: * -> *).
MonadIO m =>
TypeValueTable -> FunPtr C_TypeValueInitFunc -> m ()
setTypeValueTableValueFree TypeValueTable
s FunPtr C_TypeValueInitFunc
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
$ TypeValueTable -> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeValueTable
s ((Ptr TypeValueTable -> IO ()) -> IO ())
-> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeValueTable
ptr -> do
    Ptr (FunPtr C_TypeValueInitFunc)
-> FunPtr C_TypeValueInitFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeValueTable
ptr Ptr TypeValueTable -> Int -> Ptr (FunPtr C_TypeValueInitFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (FunPtr C_TypeValueInitFunc
val :: FunPtr GObject.Callbacks.C_TypeValueFreeFunc)

-- | Set the value of the “@value_free@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #valueFree
-- @
clearTypeValueTableValueFree :: MonadIO m => TypeValueTable -> m ()
clearTypeValueTableValueFree :: forall (m :: * -> *). MonadIO m => TypeValueTable -> m ()
clearTypeValueTableValueFree TypeValueTable
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
$ TypeValueTable -> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeValueTable
s ((Ptr TypeValueTable -> IO ()) -> IO ())
-> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeValueTable
ptr -> do
    Ptr (FunPtr C_TypeValueInitFunc)
-> FunPtr C_TypeValueInitFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeValueTable
ptr Ptr TypeValueTable -> Int -> Ptr (FunPtr C_TypeValueInitFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (FunPtr C_TypeValueInitFunc
forall a. FunPtr a
FP.nullFunPtr :: FunPtr GObject.Callbacks.C_TypeValueFreeFunc)

#if defined(ENABLE_OVERLOADING)
data TypeValueTableValueFreeFieldInfo
instance AttrInfo TypeValueTableValueFreeFieldInfo where
    type AttrBaseTypeConstraint TypeValueTableValueFreeFieldInfo = (~) TypeValueTable
    type AttrAllowedOps TypeValueTableValueFreeFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TypeValueTableValueFreeFieldInfo = (~) (FunPtr GObject.Callbacks.C_TypeValueFreeFunc)
    type AttrTransferTypeConstraint TypeValueTableValueFreeFieldInfo = (~)GObject.Callbacks.TypeValueFreeFunc
    type AttrTransferType TypeValueTableValueFreeFieldInfo = (FunPtr GObject.Callbacks.C_TypeValueFreeFunc)
    type AttrGetType TypeValueTableValueFreeFieldInfo = Maybe GObject.Callbacks.TypeValueFreeFunc
    type AttrLabel TypeValueTableValueFreeFieldInfo = "value_free"
    type AttrOrigin TypeValueTableValueFreeFieldInfo = TypeValueTable
    attrGet = getTypeValueTableValueFree
    attrSet = setTypeValueTableValueFree
    attrConstruct = undefined
    attrClear = clearTypeValueTableValueFree
    attrTransfer _ v = do
        GObject.Callbacks.mk_TypeValueFreeFunc (GObject.Callbacks.wrap_TypeValueFreeFunc Nothing v)
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GObject.Structs.TypeValueTable.valueFree"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.31/docs/GI-GObject-Structs-TypeValueTable.html#g:attr:valueFree"
        })

typeValueTable_valueFree :: AttrLabelProxy "valueFree"
typeValueTable_valueFree = AttrLabelProxy

#endif


-- | Get the value of the “@value_copy@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' typeValueTable #valueCopy
-- @
getTypeValueTableValueCopy :: MonadIO m => TypeValueTable -> m (Maybe GObject.Callbacks.TypeValueCopyFunc)
getTypeValueTableValueCopy :: forall (m :: * -> *).
MonadIO m =>
TypeValueTable -> m (Maybe TypeValueCopyFunc)
getTypeValueTableValueCopy TypeValueTable
s = IO (Maybe TypeValueCopyFunc) -> m (Maybe TypeValueCopyFunc)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TypeValueCopyFunc) -> m (Maybe TypeValueCopyFunc))
-> IO (Maybe TypeValueCopyFunc) -> m (Maybe TypeValueCopyFunc)
forall a b. (a -> b) -> a -> b
$ TypeValueTable
-> (Ptr TypeValueTable -> IO (Maybe TypeValueCopyFunc))
-> IO (Maybe TypeValueCopyFunc)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeValueTable
s ((Ptr TypeValueTable -> IO (Maybe TypeValueCopyFunc))
 -> IO (Maybe TypeValueCopyFunc))
-> (Ptr TypeValueTable -> IO (Maybe TypeValueCopyFunc))
-> IO (Maybe TypeValueCopyFunc)
forall a b. (a -> b) -> a -> b
$ \Ptr TypeValueTable
ptr -> do
    FunPtr C_TypeValueCopyFunc
val <- Ptr (FunPtr C_TypeValueCopyFunc) -> IO (FunPtr C_TypeValueCopyFunc)
forall a. Storable a => Ptr a -> IO a
peek (Ptr TypeValueTable
ptr Ptr TypeValueTable -> Int -> Ptr (FunPtr C_TypeValueCopyFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO (FunPtr GObject.Callbacks.C_TypeValueCopyFunc)
    Maybe TypeValueCopyFunc
result <- FunPtr C_TypeValueCopyFunc
-> (FunPtr C_TypeValueCopyFunc -> IO TypeValueCopyFunc)
-> IO (Maybe TypeValueCopyFunc)
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr C_TypeValueCopyFunc
val ((FunPtr C_TypeValueCopyFunc -> IO TypeValueCopyFunc)
 -> IO (Maybe TypeValueCopyFunc))
-> (FunPtr C_TypeValueCopyFunc -> IO TypeValueCopyFunc)
-> IO (Maybe TypeValueCopyFunc)
forall a b. (a -> b) -> a -> b
$ \FunPtr C_TypeValueCopyFunc
val' -> do
        let val'' :: TypeValueCopyFunc
val'' = FunPtr C_TypeValueCopyFunc -> TypeValueCopyFunc
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_TypeValueCopyFunc -> GValue -> m GValue
GObject.Callbacks.dynamic_TypeValueCopyFunc FunPtr C_TypeValueCopyFunc
val'
        TypeValueCopyFunc -> IO TypeValueCopyFunc
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TypeValueCopyFunc
val''
    Maybe TypeValueCopyFunc -> IO (Maybe TypeValueCopyFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TypeValueCopyFunc
result

-- | Set the value of the “@value_copy@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' typeValueTable [ #valueCopy 'Data.GI.Base.Attributes.:=' value ]
-- @
setTypeValueTableValueCopy :: MonadIO m => TypeValueTable -> FunPtr GObject.Callbacks.C_TypeValueCopyFunc -> m ()
setTypeValueTableValueCopy :: forall (m :: * -> *).
MonadIO m =>
TypeValueTable -> FunPtr C_TypeValueCopyFunc -> m ()
setTypeValueTableValueCopy TypeValueTable
s FunPtr C_TypeValueCopyFunc
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
$ TypeValueTable -> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeValueTable
s ((Ptr TypeValueTable -> IO ()) -> IO ())
-> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeValueTable
ptr -> do
    Ptr (FunPtr C_TypeValueCopyFunc)
-> FunPtr C_TypeValueCopyFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeValueTable
ptr Ptr TypeValueTable -> Int -> Ptr (FunPtr C_TypeValueCopyFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (FunPtr C_TypeValueCopyFunc
val :: FunPtr GObject.Callbacks.C_TypeValueCopyFunc)

-- | Set the value of the “@value_copy@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #valueCopy
-- @
clearTypeValueTableValueCopy :: MonadIO m => TypeValueTable -> m ()
clearTypeValueTableValueCopy :: forall (m :: * -> *). MonadIO m => TypeValueTable -> m ()
clearTypeValueTableValueCopy TypeValueTable
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
$ TypeValueTable -> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeValueTable
s ((Ptr TypeValueTable -> IO ()) -> IO ())
-> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeValueTable
ptr -> do
    Ptr (FunPtr C_TypeValueCopyFunc)
-> FunPtr C_TypeValueCopyFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeValueTable
ptr Ptr TypeValueTable -> Int -> Ptr (FunPtr C_TypeValueCopyFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (FunPtr C_TypeValueCopyFunc
forall a. FunPtr a
FP.nullFunPtr :: FunPtr GObject.Callbacks.C_TypeValueCopyFunc)

#if defined(ENABLE_OVERLOADING)
data TypeValueTableValueCopyFieldInfo
instance AttrInfo TypeValueTableValueCopyFieldInfo where
    type AttrBaseTypeConstraint TypeValueTableValueCopyFieldInfo = (~) TypeValueTable
    type AttrAllowedOps TypeValueTableValueCopyFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TypeValueTableValueCopyFieldInfo = (~) (FunPtr GObject.Callbacks.C_TypeValueCopyFunc)
    type AttrTransferTypeConstraint TypeValueTableValueCopyFieldInfo = (~)GObject.Callbacks.TypeValueCopyFunc
    type AttrTransferType TypeValueTableValueCopyFieldInfo = (FunPtr GObject.Callbacks.C_TypeValueCopyFunc)
    type AttrGetType TypeValueTableValueCopyFieldInfo = Maybe GObject.Callbacks.TypeValueCopyFunc
    type AttrLabel TypeValueTableValueCopyFieldInfo = "value_copy"
    type AttrOrigin TypeValueTableValueCopyFieldInfo = TypeValueTable
    attrGet = getTypeValueTableValueCopy
    attrSet = setTypeValueTableValueCopy
    attrConstruct = undefined
    attrClear = clearTypeValueTableValueCopy
    attrTransfer _ v = do
        GObject.Callbacks.mk_TypeValueCopyFunc (GObject.Callbacks.wrap_TypeValueCopyFunc Nothing v)
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GObject.Structs.TypeValueTable.valueCopy"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.31/docs/GI-GObject-Structs-TypeValueTable.html#g:attr:valueCopy"
        })

typeValueTable_valueCopy :: AttrLabelProxy "valueCopy"
typeValueTable_valueCopy = AttrLabelProxy

#endif


-- | Get the value of the “@value_peek_pointer@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' typeValueTable #valuePeekPointer
-- @
getTypeValueTableValuePeekPointer :: MonadIO m => TypeValueTable -> m (Maybe GObject.Callbacks.TypeValuePeekPointerFunc)
getTypeValueTableValuePeekPointer :: forall (m :: * -> *).
MonadIO m =>
TypeValueTable -> m (Maybe TypeValuePeekPointerFunc)
getTypeValueTableValuePeekPointer TypeValueTable
s = IO (Maybe TypeValuePeekPointerFunc)
-> m (Maybe TypeValuePeekPointerFunc)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TypeValuePeekPointerFunc)
 -> m (Maybe TypeValuePeekPointerFunc))
-> IO (Maybe TypeValuePeekPointerFunc)
-> m (Maybe TypeValuePeekPointerFunc)
forall a b. (a -> b) -> a -> b
$ TypeValueTable
-> (Ptr TypeValueTable -> IO (Maybe TypeValuePeekPointerFunc))
-> IO (Maybe TypeValuePeekPointerFunc)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeValueTable
s ((Ptr TypeValueTable -> IO (Maybe TypeValuePeekPointerFunc))
 -> IO (Maybe TypeValuePeekPointerFunc))
-> (Ptr TypeValueTable -> IO (Maybe TypeValuePeekPointerFunc))
-> IO (Maybe TypeValuePeekPointerFunc)
forall a b. (a -> b) -> a -> b
$ \Ptr TypeValueTable
ptr -> do
    FunPtr C_TypeValuePeekPointerFunc
val <- Ptr (FunPtr C_TypeValuePeekPointerFunc)
-> IO (FunPtr C_TypeValuePeekPointerFunc)
forall a. Storable a => Ptr a -> IO a
peek (Ptr TypeValueTable
ptr Ptr TypeValueTable
-> Int -> Ptr (FunPtr C_TypeValuePeekPointerFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) :: IO (FunPtr GObject.Callbacks.C_TypeValuePeekPointerFunc)
    Maybe TypeValuePeekPointerFunc
result <- FunPtr C_TypeValuePeekPointerFunc
-> (FunPtr C_TypeValuePeekPointerFunc
    -> IO TypeValuePeekPointerFunc)
-> IO (Maybe TypeValuePeekPointerFunc)
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr C_TypeValuePeekPointerFunc
val ((FunPtr C_TypeValuePeekPointerFunc -> IO TypeValuePeekPointerFunc)
 -> IO (Maybe TypeValuePeekPointerFunc))
-> (FunPtr C_TypeValuePeekPointerFunc
    -> IO TypeValuePeekPointerFunc)
-> IO (Maybe TypeValuePeekPointerFunc)
forall a b. (a -> b) -> a -> b
$ \FunPtr C_TypeValuePeekPointerFunc
val' -> do
        let val'' :: TypeValuePeekPointerFunc
val'' = FunPtr C_TypeValuePeekPointerFunc -> TypeValuePeekPointerFunc
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_TypeValuePeekPointerFunc -> GValue -> m (Ptr ())
GObject.Callbacks.dynamic_TypeValuePeekPointerFunc FunPtr C_TypeValuePeekPointerFunc
val'
        TypeValuePeekPointerFunc -> IO TypeValuePeekPointerFunc
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TypeValuePeekPointerFunc
val''
    Maybe TypeValuePeekPointerFunc
-> IO (Maybe TypeValuePeekPointerFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TypeValuePeekPointerFunc
result

-- | Set the value of the “@value_peek_pointer@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' typeValueTable [ #valuePeekPointer 'Data.GI.Base.Attributes.:=' value ]
-- @
setTypeValueTableValuePeekPointer :: MonadIO m => TypeValueTable -> FunPtr GObject.Callbacks.C_TypeValuePeekPointerFunc -> m ()
setTypeValueTableValuePeekPointer :: forall (m :: * -> *).
MonadIO m =>
TypeValueTable -> FunPtr C_TypeValuePeekPointerFunc -> m ()
setTypeValueTableValuePeekPointer TypeValueTable
s FunPtr C_TypeValuePeekPointerFunc
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
$ TypeValueTable -> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeValueTable
s ((Ptr TypeValueTable -> IO ()) -> IO ())
-> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeValueTable
ptr -> do
    Ptr (FunPtr C_TypeValuePeekPointerFunc)
-> FunPtr C_TypeValuePeekPointerFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeValueTable
ptr Ptr TypeValueTable
-> Int -> Ptr (FunPtr C_TypeValuePeekPointerFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (FunPtr C_TypeValuePeekPointerFunc
val :: FunPtr GObject.Callbacks.C_TypeValuePeekPointerFunc)

-- | Set the value of the “@value_peek_pointer@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #valuePeekPointer
-- @
clearTypeValueTableValuePeekPointer :: MonadIO m => TypeValueTable -> m ()
clearTypeValueTableValuePeekPointer :: forall (m :: * -> *). MonadIO m => TypeValueTable -> m ()
clearTypeValueTableValuePeekPointer TypeValueTable
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
$ TypeValueTable -> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeValueTable
s ((Ptr TypeValueTable -> IO ()) -> IO ())
-> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeValueTable
ptr -> do
    Ptr (FunPtr C_TypeValuePeekPointerFunc)
-> FunPtr C_TypeValuePeekPointerFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeValueTable
ptr Ptr TypeValueTable
-> Int -> Ptr (FunPtr C_TypeValuePeekPointerFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (FunPtr C_TypeValuePeekPointerFunc
forall a. FunPtr a
FP.nullFunPtr :: FunPtr GObject.Callbacks.C_TypeValuePeekPointerFunc)

#if defined(ENABLE_OVERLOADING)
data TypeValueTableValuePeekPointerFieldInfo
instance AttrInfo TypeValueTableValuePeekPointerFieldInfo where
    type AttrBaseTypeConstraint TypeValueTableValuePeekPointerFieldInfo = (~) TypeValueTable
    type AttrAllowedOps TypeValueTableValuePeekPointerFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TypeValueTableValuePeekPointerFieldInfo = (~) (FunPtr GObject.Callbacks.C_TypeValuePeekPointerFunc)
    type AttrTransferTypeConstraint TypeValueTableValuePeekPointerFieldInfo = (~)GObject.Callbacks.TypeValuePeekPointerFunc
    type AttrTransferType TypeValueTableValuePeekPointerFieldInfo = (FunPtr GObject.Callbacks.C_TypeValuePeekPointerFunc)
    type AttrGetType TypeValueTableValuePeekPointerFieldInfo = Maybe GObject.Callbacks.TypeValuePeekPointerFunc
    type AttrLabel TypeValueTableValuePeekPointerFieldInfo = "value_peek_pointer"
    type AttrOrigin TypeValueTableValuePeekPointerFieldInfo = TypeValueTable
    attrGet = getTypeValueTableValuePeekPointer
    attrSet = setTypeValueTableValuePeekPointer
    attrConstruct = undefined
    attrClear = clearTypeValueTableValuePeekPointer
    attrTransfer _ v = do
        GObject.Callbacks.mk_TypeValuePeekPointerFunc (GObject.Callbacks.wrap_TypeValuePeekPointerFunc Nothing v)
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GObject.Structs.TypeValueTable.valuePeekPointer"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.31/docs/GI-GObject-Structs-TypeValueTable.html#g:attr:valuePeekPointer"
        })

typeValueTable_valuePeekPointer :: AttrLabelProxy "valuePeekPointer"
typeValueTable_valuePeekPointer = AttrLabelProxy

#endif


-- | Get the value of the “@collect_format@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' typeValueTable #collectFormat
-- @
getTypeValueTableCollectFormat :: MonadIO m => TypeValueTable -> m (Maybe T.Text)
getTypeValueTableCollectFormat :: forall (m :: * -> *). MonadIO m => TypeValueTable -> m (Maybe Text)
getTypeValueTableCollectFormat TypeValueTable
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
$ TypeValueTable
-> (Ptr TypeValueTable -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeValueTable
s ((Ptr TypeValueTable -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr TypeValueTable -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr TypeValueTable
ptr -> do
    CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr TypeValueTable
ptr Ptr TypeValueTable -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) :: 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
$ \CString
val' -> do
        Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result

-- | Set the value of the “@collect_format@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' typeValueTable [ #collectFormat 'Data.GI.Base.Attributes.:=' value ]
-- @
setTypeValueTableCollectFormat :: MonadIO m => TypeValueTable -> CString -> m ()
setTypeValueTableCollectFormat :: forall (m :: * -> *).
MonadIO m =>
TypeValueTable -> CString -> m ()
setTypeValueTableCollectFormat TypeValueTable
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
$ TypeValueTable -> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeValueTable
s ((Ptr TypeValueTable -> IO ()) -> IO ())
-> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeValueTable
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeValueTable
ptr Ptr TypeValueTable -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) (CString
val :: CString)

-- | Set the value of the “@collect_format@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #collectFormat
-- @
clearTypeValueTableCollectFormat :: MonadIO m => TypeValueTable -> m ()
clearTypeValueTableCollectFormat :: forall (m :: * -> *). MonadIO m => TypeValueTable -> m ()
clearTypeValueTableCollectFormat TypeValueTable
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
$ TypeValueTable -> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeValueTable
s ((Ptr TypeValueTable -> IO ()) -> IO ())
-> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeValueTable
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeValueTable
ptr Ptr TypeValueTable -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) (CString
forall a. Ptr a
FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING)
data TypeValueTableCollectFormatFieldInfo
instance AttrInfo TypeValueTableCollectFormatFieldInfo where
    type AttrBaseTypeConstraint TypeValueTableCollectFormatFieldInfo = (~) TypeValueTable
    type AttrAllowedOps TypeValueTableCollectFormatFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TypeValueTableCollectFormatFieldInfo = (~) CString
    type AttrTransferTypeConstraint TypeValueTableCollectFormatFieldInfo = (~)CString
    type AttrTransferType TypeValueTableCollectFormatFieldInfo = CString
    type AttrGetType TypeValueTableCollectFormatFieldInfo = Maybe T.Text
    type AttrLabel TypeValueTableCollectFormatFieldInfo = "collect_format"
    type AttrOrigin TypeValueTableCollectFormatFieldInfo = TypeValueTable
    attrGet = getTypeValueTableCollectFormat
    attrSet = setTypeValueTableCollectFormat
    attrConstruct = undefined
    attrClear = clearTypeValueTableCollectFormat
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GObject.Structs.TypeValueTable.collectFormat"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.31/docs/GI-GObject-Structs-TypeValueTable.html#g:attr:collectFormat"
        })

typeValueTable_collectFormat :: AttrLabelProxy "collectFormat"
typeValueTable_collectFormat = AttrLabelProxy

#endif


-- | Get the value of the “@collect_value@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' typeValueTable #collectValue
-- @
getTypeValueTableCollectValue :: MonadIO m => TypeValueTable -> m (Maybe GObject.Callbacks.TypeValueCollectFunc)
getTypeValueTableCollectValue :: forall (m :: * -> *).
MonadIO m =>
TypeValueTable -> m (Maybe TypeValueCollectFunc)
getTypeValueTableCollectValue TypeValueTable
s = IO (Maybe TypeValueCollectFunc) -> m (Maybe TypeValueCollectFunc)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TypeValueCollectFunc) -> m (Maybe TypeValueCollectFunc))
-> IO (Maybe TypeValueCollectFunc)
-> m (Maybe TypeValueCollectFunc)
forall a b. (a -> b) -> a -> b
$ TypeValueTable
-> (Ptr TypeValueTable -> IO (Maybe TypeValueCollectFunc))
-> IO (Maybe TypeValueCollectFunc)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeValueTable
s ((Ptr TypeValueTable -> IO (Maybe TypeValueCollectFunc))
 -> IO (Maybe TypeValueCollectFunc))
-> (Ptr TypeValueTable -> IO (Maybe TypeValueCollectFunc))
-> IO (Maybe TypeValueCollectFunc)
forall a b. (a -> b) -> a -> b
$ \Ptr TypeValueTable
ptr -> do
    FunPtr C_TypeValueCollectFunc
val <- Ptr (FunPtr C_TypeValueCollectFunc)
-> IO (FunPtr C_TypeValueCollectFunc)
forall a. Storable a => Ptr a -> IO a
peek (Ptr TypeValueTable
ptr Ptr TypeValueTable -> Int -> Ptr (FunPtr C_TypeValueCollectFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40) :: IO (FunPtr GObject.Callbacks.C_TypeValueCollectFunc)
    Maybe TypeValueCollectFunc
result <- FunPtr C_TypeValueCollectFunc
-> (FunPtr C_TypeValueCollectFunc -> IO TypeValueCollectFunc)
-> IO (Maybe TypeValueCollectFunc)
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr C_TypeValueCollectFunc
val ((FunPtr C_TypeValueCollectFunc -> IO TypeValueCollectFunc)
 -> IO (Maybe TypeValueCollectFunc))
-> (FunPtr C_TypeValueCollectFunc -> IO TypeValueCollectFunc)
-> IO (Maybe TypeValueCollectFunc)
forall a b. (a -> b) -> a -> b
$ \FunPtr C_TypeValueCollectFunc
val' -> do
        let val'' :: TypeValueCollectFunc
val'' = FunPtr C_TypeValueCollectFunc -> TypeValueCollectFunc
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_TypeValueCollectFunc
-> GValue -> [TypeCValue] -> Word32 -> m (Maybe Text)
GObject.Callbacks.dynamic_TypeValueCollectFunc FunPtr C_TypeValueCollectFunc
val'
        TypeValueCollectFunc -> IO TypeValueCollectFunc
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TypeValueCollectFunc
val''
    Maybe TypeValueCollectFunc -> IO (Maybe TypeValueCollectFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TypeValueCollectFunc
result

-- | Set the value of the “@collect_value@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' typeValueTable [ #collectValue 'Data.GI.Base.Attributes.:=' value ]
-- @
setTypeValueTableCollectValue :: MonadIO m => TypeValueTable -> FunPtr GObject.Callbacks.C_TypeValueCollectFunc -> m ()
setTypeValueTableCollectValue :: forall (m :: * -> *).
MonadIO m =>
TypeValueTable -> FunPtr C_TypeValueCollectFunc -> m ()
setTypeValueTableCollectValue TypeValueTable
s FunPtr C_TypeValueCollectFunc
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
$ TypeValueTable -> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeValueTable
s ((Ptr TypeValueTable -> IO ()) -> IO ())
-> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeValueTable
ptr -> do
    Ptr (FunPtr C_TypeValueCollectFunc)
-> FunPtr C_TypeValueCollectFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeValueTable
ptr Ptr TypeValueTable -> Int -> Ptr (FunPtr C_TypeValueCollectFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40) (FunPtr C_TypeValueCollectFunc
val :: FunPtr GObject.Callbacks.C_TypeValueCollectFunc)

-- | Set the value of the “@collect_value@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #collectValue
-- @
clearTypeValueTableCollectValue :: MonadIO m => TypeValueTable -> m ()
clearTypeValueTableCollectValue :: forall (m :: * -> *). MonadIO m => TypeValueTable -> m ()
clearTypeValueTableCollectValue TypeValueTable
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
$ TypeValueTable -> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeValueTable
s ((Ptr TypeValueTable -> IO ()) -> IO ())
-> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeValueTable
ptr -> do
    Ptr (FunPtr C_TypeValueCollectFunc)
-> FunPtr C_TypeValueCollectFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeValueTable
ptr Ptr TypeValueTable -> Int -> Ptr (FunPtr C_TypeValueCollectFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40) (FunPtr C_TypeValueCollectFunc
forall a. FunPtr a
FP.nullFunPtr :: FunPtr GObject.Callbacks.C_TypeValueCollectFunc)

#if defined(ENABLE_OVERLOADING)
data TypeValueTableCollectValueFieldInfo
instance AttrInfo TypeValueTableCollectValueFieldInfo where
    type AttrBaseTypeConstraint TypeValueTableCollectValueFieldInfo = (~) TypeValueTable
    type AttrAllowedOps TypeValueTableCollectValueFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TypeValueTableCollectValueFieldInfo = (~) (FunPtr GObject.Callbacks.C_TypeValueCollectFunc)
    type AttrTransferTypeConstraint TypeValueTableCollectValueFieldInfo = (~)GObject.Callbacks.TypeValueCollectFunc
    type AttrTransferType TypeValueTableCollectValueFieldInfo = (FunPtr GObject.Callbacks.C_TypeValueCollectFunc)
    type AttrGetType TypeValueTableCollectValueFieldInfo = Maybe GObject.Callbacks.TypeValueCollectFunc
    type AttrLabel TypeValueTableCollectValueFieldInfo = "collect_value"
    type AttrOrigin TypeValueTableCollectValueFieldInfo = TypeValueTable
    attrGet = getTypeValueTableCollectValue
    attrSet = setTypeValueTableCollectValue
    attrConstruct = undefined
    attrClear = clearTypeValueTableCollectValue
    attrTransfer _ v = do
        GObject.Callbacks.mk_TypeValueCollectFunc (GObject.Callbacks.wrap_TypeValueCollectFunc Nothing v)
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GObject.Structs.TypeValueTable.collectValue"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.31/docs/GI-GObject-Structs-TypeValueTable.html#g:attr:collectValue"
        })

typeValueTable_collectValue :: AttrLabelProxy "collectValue"
typeValueTable_collectValue = AttrLabelProxy

#endif


-- | Get the value of the “@lcopy_format@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' typeValueTable #lcopyFormat
-- @
getTypeValueTableLcopyFormat :: MonadIO m => TypeValueTable -> m (Maybe T.Text)
getTypeValueTableLcopyFormat :: forall (m :: * -> *). MonadIO m => TypeValueTable -> m (Maybe Text)
getTypeValueTableLcopyFormat TypeValueTable
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
$ TypeValueTable
-> (Ptr TypeValueTable -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeValueTable
s ((Ptr TypeValueTable -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr TypeValueTable -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr TypeValueTable
ptr -> do
    CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr TypeValueTable
ptr Ptr TypeValueTable -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48) :: 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
$ \CString
val' -> do
        Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result

-- | Set the value of the “@lcopy_format@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' typeValueTable [ #lcopyFormat 'Data.GI.Base.Attributes.:=' value ]
-- @
setTypeValueTableLcopyFormat :: MonadIO m => TypeValueTable -> CString -> m ()
setTypeValueTableLcopyFormat :: forall (m :: * -> *).
MonadIO m =>
TypeValueTable -> CString -> m ()
setTypeValueTableLcopyFormat TypeValueTable
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
$ TypeValueTable -> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeValueTable
s ((Ptr TypeValueTable -> IO ()) -> IO ())
-> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeValueTable
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeValueTable
ptr Ptr TypeValueTable -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48) (CString
val :: CString)

-- | Set the value of the “@lcopy_format@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #lcopyFormat
-- @
clearTypeValueTableLcopyFormat :: MonadIO m => TypeValueTable -> m ()
clearTypeValueTableLcopyFormat :: forall (m :: * -> *). MonadIO m => TypeValueTable -> m ()
clearTypeValueTableLcopyFormat TypeValueTable
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
$ TypeValueTable -> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeValueTable
s ((Ptr TypeValueTable -> IO ()) -> IO ())
-> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeValueTable
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeValueTable
ptr Ptr TypeValueTable -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48) (CString
forall a. Ptr a
FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING)
data TypeValueTableLcopyFormatFieldInfo
instance AttrInfo TypeValueTableLcopyFormatFieldInfo where
    type AttrBaseTypeConstraint TypeValueTableLcopyFormatFieldInfo = (~) TypeValueTable
    type AttrAllowedOps TypeValueTableLcopyFormatFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TypeValueTableLcopyFormatFieldInfo = (~) CString
    type AttrTransferTypeConstraint TypeValueTableLcopyFormatFieldInfo = (~)CString
    type AttrTransferType TypeValueTableLcopyFormatFieldInfo = CString
    type AttrGetType TypeValueTableLcopyFormatFieldInfo = Maybe T.Text
    type AttrLabel TypeValueTableLcopyFormatFieldInfo = "lcopy_format"
    type AttrOrigin TypeValueTableLcopyFormatFieldInfo = TypeValueTable
    attrGet = getTypeValueTableLcopyFormat
    attrSet = setTypeValueTableLcopyFormat
    attrConstruct = undefined
    attrClear = clearTypeValueTableLcopyFormat
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GObject.Structs.TypeValueTable.lcopyFormat"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.31/docs/GI-GObject-Structs-TypeValueTable.html#g:attr:lcopyFormat"
        })

typeValueTable_lcopyFormat :: AttrLabelProxy "lcopyFormat"
typeValueTable_lcopyFormat = AttrLabelProxy

#endif


-- | Get the value of the “@lcopy_value@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' typeValueTable #lcopyValue
-- @
getTypeValueTableLcopyValue :: MonadIO m => TypeValueTable -> m (Maybe GObject.Callbacks.TypeValueLCopyFunc)
getTypeValueTableLcopyValue :: forall (m :: * -> *).
MonadIO m =>
TypeValueTable -> m (Maybe TypeValueCollectFunc)
getTypeValueTableLcopyValue TypeValueTable
s = IO (Maybe TypeValueCollectFunc) -> m (Maybe TypeValueCollectFunc)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TypeValueCollectFunc) -> m (Maybe TypeValueCollectFunc))
-> IO (Maybe TypeValueCollectFunc)
-> m (Maybe TypeValueCollectFunc)
forall a b. (a -> b) -> a -> b
$ TypeValueTable
-> (Ptr TypeValueTable -> IO (Maybe TypeValueCollectFunc))
-> IO (Maybe TypeValueCollectFunc)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeValueTable
s ((Ptr TypeValueTable -> IO (Maybe TypeValueCollectFunc))
 -> IO (Maybe TypeValueCollectFunc))
-> (Ptr TypeValueTable -> IO (Maybe TypeValueCollectFunc))
-> IO (Maybe TypeValueCollectFunc)
forall a b. (a -> b) -> a -> b
$ \Ptr TypeValueTable
ptr -> do
    FunPtr C_TypeValueCollectFunc
val <- Ptr (FunPtr C_TypeValueCollectFunc)
-> IO (FunPtr C_TypeValueCollectFunc)
forall a. Storable a => Ptr a -> IO a
peek (Ptr TypeValueTable
ptr Ptr TypeValueTable -> Int -> Ptr (FunPtr C_TypeValueCollectFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56) :: IO (FunPtr GObject.Callbacks.C_TypeValueLCopyFunc)
    Maybe TypeValueCollectFunc
result <- FunPtr C_TypeValueCollectFunc
-> (FunPtr C_TypeValueCollectFunc -> IO TypeValueCollectFunc)
-> IO (Maybe TypeValueCollectFunc)
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr C_TypeValueCollectFunc
val ((FunPtr C_TypeValueCollectFunc -> IO TypeValueCollectFunc)
 -> IO (Maybe TypeValueCollectFunc))
-> (FunPtr C_TypeValueCollectFunc -> IO TypeValueCollectFunc)
-> IO (Maybe TypeValueCollectFunc)
forall a b. (a -> b) -> a -> b
$ \FunPtr C_TypeValueCollectFunc
val' -> do
        let val'' :: TypeValueCollectFunc
val'' = FunPtr C_TypeValueCollectFunc -> TypeValueCollectFunc
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_TypeValueCollectFunc
-> GValue -> [TypeCValue] -> Word32 -> m (Maybe Text)
GObject.Callbacks.dynamic_TypeValueLCopyFunc FunPtr C_TypeValueCollectFunc
val'
        TypeValueCollectFunc -> IO TypeValueCollectFunc
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TypeValueCollectFunc
val''
    Maybe TypeValueCollectFunc -> IO (Maybe TypeValueCollectFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TypeValueCollectFunc
result

-- | Set the value of the “@lcopy_value@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' typeValueTable [ #lcopyValue 'Data.GI.Base.Attributes.:=' value ]
-- @
setTypeValueTableLcopyValue :: MonadIO m => TypeValueTable -> FunPtr GObject.Callbacks.C_TypeValueLCopyFunc -> m ()
setTypeValueTableLcopyValue :: forall (m :: * -> *).
MonadIO m =>
TypeValueTable -> FunPtr C_TypeValueCollectFunc -> m ()
setTypeValueTableLcopyValue TypeValueTable
s FunPtr C_TypeValueCollectFunc
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
$ TypeValueTable -> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeValueTable
s ((Ptr TypeValueTable -> IO ()) -> IO ())
-> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeValueTable
ptr -> do
    Ptr (FunPtr C_TypeValueCollectFunc)
-> FunPtr C_TypeValueCollectFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeValueTable
ptr Ptr TypeValueTable -> Int -> Ptr (FunPtr C_TypeValueCollectFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56) (FunPtr C_TypeValueCollectFunc
val :: FunPtr GObject.Callbacks.C_TypeValueLCopyFunc)

-- | Set the value of the “@lcopy_value@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #lcopyValue
-- @
clearTypeValueTableLcopyValue :: MonadIO m => TypeValueTable -> m ()
clearTypeValueTableLcopyValue :: forall (m :: * -> *). MonadIO m => TypeValueTable -> m ()
clearTypeValueTableLcopyValue TypeValueTable
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
$ TypeValueTable -> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeValueTable
s ((Ptr TypeValueTable -> IO ()) -> IO ())
-> (Ptr TypeValueTable -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeValueTable
ptr -> do
    Ptr (FunPtr C_TypeValueCollectFunc)
-> FunPtr C_TypeValueCollectFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeValueTable
ptr Ptr TypeValueTable -> Int -> Ptr (FunPtr C_TypeValueCollectFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56) (FunPtr C_TypeValueCollectFunc
forall a. FunPtr a
FP.nullFunPtr :: FunPtr GObject.Callbacks.C_TypeValueLCopyFunc)

#if defined(ENABLE_OVERLOADING)
data TypeValueTableLcopyValueFieldInfo
instance AttrInfo TypeValueTableLcopyValueFieldInfo where
    type AttrBaseTypeConstraint TypeValueTableLcopyValueFieldInfo = (~) TypeValueTable
    type AttrAllowedOps TypeValueTableLcopyValueFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TypeValueTableLcopyValueFieldInfo = (~) (FunPtr GObject.Callbacks.C_TypeValueLCopyFunc)
    type AttrTransferTypeConstraint TypeValueTableLcopyValueFieldInfo = (~)GObject.Callbacks.TypeValueLCopyFunc
    type AttrTransferType TypeValueTableLcopyValueFieldInfo = (FunPtr GObject.Callbacks.C_TypeValueLCopyFunc)
    type AttrGetType TypeValueTableLcopyValueFieldInfo = Maybe GObject.Callbacks.TypeValueLCopyFunc
    type AttrLabel TypeValueTableLcopyValueFieldInfo = "lcopy_value"
    type AttrOrigin TypeValueTableLcopyValueFieldInfo = TypeValueTable
    attrGet = getTypeValueTableLcopyValue
    attrSet = setTypeValueTableLcopyValue
    attrConstruct = undefined
    attrClear = clearTypeValueTableLcopyValue
    attrTransfer _ v = do
        GObject.Callbacks.mk_TypeValueLCopyFunc (GObject.Callbacks.wrap_TypeValueLCopyFunc Nothing v)
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GObject.Structs.TypeValueTable.lcopyValue"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.31/docs/GI-GObject-Structs-TypeValueTable.html#g:attr:lcopyValue"
        })

typeValueTable_lcopyValue :: AttrLabelProxy "lcopyValue"
typeValueTable_lcopyValue = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TypeValueTable
type instance O.AttributeList TypeValueTable = TypeValueTableAttributeList
type TypeValueTableAttributeList = ('[ '("valueInit", TypeValueTableValueInitFieldInfo), '("valueFree", TypeValueTableValueFreeFieldInfo), '("valueCopy", TypeValueTableValueCopyFieldInfo), '("valuePeekPointer", TypeValueTableValuePeekPointerFieldInfo), '("collectFormat", TypeValueTableCollectFormatFieldInfo), '("collectValue", TypeValueTableCollectValueFieldInfo), '("lcopyFormat", TypeValueTableLcopyFormatFieldInfo), '("lcopyValue", TypeValueTableLcopyValueFieldInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveTypeValueTableMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveTypeValueTableMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveTypeValueTableMethod t TypeValueTable, O.OverloadedMethod info TypeValueTable p) => OL.IsLabel t (TypeValueTable -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveTypeValueTableMethod t TypeValueTable, O.OverloadedMethod info TypeValueTable p, R.HasField t TypeValueTable p) => R.HasField t TypeValueTable p where
    getField = O.overloadedMethod @info

#endif

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

#endif