{-# LANGUAGE TypeApplications #-}


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


 -- * Methods
-- ** Overloaded methods #method:Overloaded 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#
-- | /No description available in the introspection data./

    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#
-- | /No description available in the introspection data./

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


-- ** valueCopy #attr:valueCopy#
-- | /No description available in the introspection data./

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


-- ** valueFree #attr:valueFree#
-- | /No description available in the introspection data./

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


-- ** valueInit #attr:valueInit#
-- | /No description available in the introspection data./

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


-- ** valuePeekPointer #attr:valuePeekPointer#
-- | /No description available in the introspection data./

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

import qualified GI.GObject.Callbacks as GObject.Callbacks

-- | Memory-managed wrapper type.
newtype TypeValueTable = TypeValueTable (ManagedPtr TypeValueTable)
    deriving (Eq)
instance WrappedPtr TypeValueTable where
    wrappedPtrCalloc = callocBytes 32
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 32 >=> wrapPtr TypeValueTable)
    wrappedPtrFree = Just ptr_to_g_free

-- | Construct a `TypeValueTable` struct initialized to zero.
newZeroTypeValueTable :: MonadIO m => m TypeValueTable
newZeroTypeValueTable = liftIO $ wrappedPtrCalloc >>= wrapPtr TypeValueTable

instance tag ~ 'AttrSet => Constructible TypeValueTable tag where
    new _ attrs = do
        o <- newZeroTypeValueTable
        GI.Attributes.set o attrs
        return o


-- | A convenience alias for `Nothing` :: `Maybe` `TypeValueTable`.
noTypeValueTable :: Maybe TypeValueTable
noTypeValueTable = Nothing

-- | 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.TypeValueTableValueInitFieldCallback)
getTypeValueTableValueInit s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO (FunPtr GObject.Callbacks.C_TypeValueTableValueInitFieldCallback)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = GObject.Callbacks.dynamic_TypeValueTableValueInitFieldCallback val'
        return val''
    return 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_TypeValueTableValueInitFieldCallback -> m ()
setTypeValueTableValueInit s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: FunPtr GObject.Callbacks.C_TypeValueTableValueInitFieldCallback)

-- | 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 s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (FP.nullFunPtr :: FunPtr GObject.Callbacks.C_TypeValueTableValueInitFieldCallback)

#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_TypeValueTableValueInitFieldCallback)
    type AttrTransferTypeConstraint TypeValueTableValueInitFieldInfo = (~)GObject.Callbacks.TypeValueTableValueInitFieldCallback
    type AttrTransferType TypeValueTableValueInitFieldInfo = (FunPtr GObject.Callbacks.C_TypeValueTableValueInitFieldCallback)
    type AttrGetType TypeValueTableValueInitFieldInfo = Maybe GObject.Callbacks.TypeValueTableValueInitFieldCallback
    type AttrLabel TypeValueTableValueInitFieldInfo = "value_init"
    type AttrOrigin TypeValueTableValueInitFieldInfo = TypeValueTable
    attrGet = getTypeValueTableValueInit
    attrSet = setTypeValueTableValueInit
    attrConstruct = undefined
    attrClear = clearTypeValueTableValueInit
    attrTransfer _ v = do
        GObject.Callbacks.mk_TypeValueTableValueInitFieldCallback (GObject.Callbacks.wrap_TypeValueTableValueInitFieldCallback Nothing v)

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.TypeValueTableValueFreeFieldCallback)
getTypeValueTableValueFree s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 4) :: IO (FunPtr GObject.Callbacks.C_TypeValueTableValueFreeFieldCallback)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = GObject.Callbacks.dynamic_TypeValueTableValueFreeFieldCallback val'
        return val''
    return 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_TypeValueTableValueFreeFieldCallback -> m ()
setTypeValueTableValueFree s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 4) (val :: FunPtr GObject.Callbacks.C_TypeValueTableValueFreeFieldCallback)

-- | 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 s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 4) (FP.nullFunPtr :: FunPtr GObject.Callbacks.C_TypeValueTableValueFreeFieldCallback)

#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_TypeValueTableValueFreeFieldCallback)
    type AttrTransferTypeConstraint TypeValueTableValueFreeFieldInfo = (~)GObject.Callbacks.TypeValueTableValueFreeFieldCallback
    type AttrTransferType TypeValueTableValueFreeFieldInfo = (FunPtr GObject.Callbacks.C_TypeValueTableValueFreeFieldCallback)
    type AttrGetType TypeValueTableValueFreeFieldInfo = Maybe GObject.Callbacks.TypeValueTableValueFreeFieldCallback
    type AttrLabel TypeValueTableValueFreeFieldInfo = "value_free"
    type AttrOrigin TypeValueTableValueFreeFieldInfo = TypeValueTable
    attrGet = getTypeValueTableValueFree
    attrSet = setTypeValueTableValueFree
    attrConstruct = undefined
    attrClear = clearTypeValueTableValueFree
    attrTransfer _ v = do
        GObject.Callbacks.mk_TypeValueTableValueFreeFieldCallback (GObject.Callbacks.wrap_TypeValueTableValueFreeFieldCallback Nothing v)

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.TypeValueTableValueCopyFieldCallback)
getTypeValueTableValueCopy s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO (FunPtr GObject.Callbacks.C_TypeValueTableValueCopyFieldCallback)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = GObject.Callbacks.dynamic_TypeValueTableValueCopyFieldCallback val'
        return val''
    return 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_TypeValueTableValueCopyFieldCallback -> m ()
setTypeValueTableValueCopy s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (val :: FunPtr GObject.Callbacks.C_TypeValueTableValueCopyFieldCallback)

-- | 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 s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullFunPtr :: FunPtr GObject.Callbacks.C_TypeValueTableValueCopyFieldCallback)

#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_TypeValueTableValueCopyFieldCallback)
    type AttrTransferTypeConstraint TypeValueTableValueCopyFieldInfo = (~)GObject.Callbacks.TypeValueTableValueCopyFieldCallback
    type AttrTransferType TypeValueTableValueCopyFieldInfo = (FunPtr GObject.Callbacks.C_TypeValueTableValueCopyFieldCallback)
    type AttrGetType TypeValueTableValueCopyFieldInfo = Maybe GObject.Callbacks.TypeValueTableValueCopyFieldCallback
    type AttrLabel TypeValueTableValueCopyFieldInfo = "value_copy"
    type AttrOrigin TypeValueTableValueCopyFieldInfo = TypeValueTable
    attrGet = getTypeValueTableValueCopy
    attrSet = setTypeValueTableValueCopy
    attrConstruct = undefined
    attrClear = clearTypeValueTableValueCopy
    attrTransfer _ v = do
        GObject.Callbacks.mk_TypeValueTableValueCopyFieldCallback (GObject.Callbacks.wrap_TypeValueTableValueCopyFieldCallback Nothing v)

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.TypeValueTableValuePeekPointerFieldCallback)
getTypeValueTableValuePeekPointer s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 12) :: IO (FunPtr GObject.Callbacks.C_TypeValueTableValuePeekPointerFieldCallback)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = GObject.Callbacks.dynamic_TypeValueTableValuePeekPointerFieldCallback val'
        return val''
    return 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_TypeValueTableValuePeekPointerFieldCallback -> m ()
setTypeValueTableValuePeekPointer s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 12) (val :: FunPtr GObject.Callbacks.C_TypeValueTableValuePeekPointerFieldCallback)

-- | 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 s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 12) (FP.nullFunPtr :: FunPtr GObject.Callbacks.C_TypeValueTableValuePeekPointerFieldCallback)

#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_TypeValueTableValuePeekPointerFieldCallback)
    type AttrTransferTypeConstraint TypeValueTableValuePeekPointerFieldInfo = (~)GObject.Callbacks.TypeValueTableValuePeekPointerFieldCallback
    type AttrTransferType TypeValueTableValuePeekPointerFieldInfo = (FunPtr GObject.Callbacks.C_TypeValueTableValuePeekPointerFieldCallback)
    type AttrGetType TypeValueTableValuePeekPointerFieldInfo = Maybe GObject.Callbacks.TypeValueTableValuePeekPointerFieldCallback
    type AttrLabel TypeValueTableValuePeekPointerFieldInfo = "value_peek_pointer"
    type AttrOrigin TypeValueTableValuePeekPointerFieldInfo = TypeValueTable
    attrGet = getTypeValueTableValuePeekPointer
    attrSet = setTypeValueTableValuePeekPointer
    attrConstruct = undefined
    attrClear = clearTypeValueTableValuePeekPointer
    attrTransfer _ v = do
        GObject.Callbacks.mk_TypeValueTableValuePeekPointerFieldCallback (GObject.Callbacks.wrap_TypeValueTableValuePeekPointerFieldCallback Nothing v)

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 s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO CString
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- cstringToText val'
        return val''
    return 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 s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (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 s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (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

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.TypeValueTableCollectValueFieldCallback)
getTypeValueTableCollectValue s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 20) :: IO (FunPtr GObject.Callbacks.C_TypeValueTableCollectValueFieldCallback)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = GObject.Callbacks.dynamic_TypeValueTableCollectValueFieldCallback val'
        return val''
    return 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_TypeValueTableCollectValueFieldCallback -> m ()
setTypeValueTableCollectValue s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 20) (val :: FunPtr GObject.Callbacks.C_TypeValueTableCollectValueFieldCallback)

-- | 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 s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 20) (FP.nullFunPtr :: FunPtr GObject.Callbacks.C_TypeValueTableCollectValueFieldCallback)

#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_TypeValueTableCollectValueFieldCallback)
    type AttrTransferTypeConstraint TypeValueTableCollectValueFieldInfo = (~)GObject.Callbacks.TypeValueTableCollectValueFieldCallback
    type AttrTransferType TypeValueTableCollectValueFieldInfo = (FunPtr GObject.Callbacks.C_TypeValueTableCollectValueFieldCallback)
    type AttrGetType TypeValueTableCollectValueFieldInfo = Maybe GObject.Callbacks.TypeValueTableCollectValueFieldCallback
    type AttrLabel TypeValueTableCollectValueFieldInfo = "collect_value"
    type AttrOrigin TypeValueTableCollectValueFieldInfo = TypeValueTable
    attrGet = getTypeValueTableCollectValue
    attrSet = setTypeValueTableCollectValue
    attrConstruct = undefined
    attrClear = clearTypeValueTableCollectValue
    attrTransfer _ v = do
        GObject.Callbacks.mk_TypeValueTableCollectValueFieldCallback (GObject.Callbacks.wrap_TypeValueTableCollectValueFieldCallback Nothing v)

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 s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO CString
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- cstringToText val'
        return val''
    return 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 s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (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 s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (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

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.TypeValueTableLcopyValueFieldCallback)
getTypeValueTableLcopyValue s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 28) :: IO (FunPtr GObject.Callbacks.C_TypeValueTableLcopyValueFieldCallback)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = GObject.Callbacks.dynamic_TypeValueTableLcopyValueFieldCallback val'
        return val''
    return 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_TypeValueTableLcopyValueFieldCallback -> m ()
setTypeValueTableLcopyValue s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 28) (val :: FunPtr GObject.Callbacks.C_TypeValueTableLcopyValueFieldCallback)

-- | 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 s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 28) (FP.nullFunPtr :: FunPtr GObject.Callbacks.C_TypeValueTableLcopyValueFieldCallback)

#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_TypeValueTableLcopyValueFieldCallback)
    type AttrTransferTypeConstraint TypeValueTableLcopyValueFieldInfo = (~)GObject.Callbacks.TypeValueTableLcopyValueFieldCallback
    type AttrTransferType TypeValueTableLcopyValueFieldInfo = (FunPtr GObject.Callbacks.C_TypeValueTableLcopyValueFieldCallback)
    type AttrGetType TypeValueTableLcopyValueFieldInfo = Maybe GObject.Callbacks.TypeValueTableLcopyValueFieldCallback
    type AttrLabel TypeValueTableLcopyValueFieldInfo = "lcopy_value"
    type AttrOrigin TypeValueTableLcopyValueFieldInfo = TypeValueTable
    attrGet = getTypeValueTableLcopyValue
    attrSet = setTypeValueTableLcopyValue
    attrConstruct = undefined
    attrClear = clearTypeValueTableLcopyValue
    attrTransfer _ v = do
        GObject.Callbacks.mk_TypeValueTableLcopyValueFieldCallback (GObject.Callbacks.wrap_TypeValueTableLcopyValueFieldCallback Nothing v)

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, *)])
#endif

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

instance (info ~ ResolveTypeValueTableMethod t TypeValueTable, O.MethodInfo 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

#endif