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

This structure is used to provide the type system with the information
required to initialize and destruct (finalize) a type\'s class and
its instances.

The initialized structure is passed to the 'GI.GObject.Functions.typeRegisterStatic' function
(or is copied into the provided 'GI.GObject.Structs.TypeInfo.TypeInfo' structure in the
'GI.GObject.Interfaces.TypePlugin.typePluginCompleteTypeInfo'). The type system will perform a deep
copy of this structure, so its memory does not need to be persistent
across invocation of 'GI.GObject.Functions.typeRegisterStatic'.
-}

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

module GI.GObject.Structs.TypeInfo
    (

-- * Exported types
    TypeInfo(..)                            ,
    newZeroTypeInfo                         ,
    noTypeInfo                              ,


 -- * Properties
-- ** baseFinalize #attr:baseFinalize#
{- | Location of the base finalization function (optional)
-}
    clearTypeInfoBaseFinalize               ,
    getTypeInfoBaseFinalize                 ,
    setTypeInfoBaseFinalize                 ,
#if ENABLE_OVERLOADING
    typeInfo_baseFinalize                   ,
#endif


-- ** baseInit #attr:baseInit#
{- | Location of the base initialization function (optional)
-}
    clearTypeInfoBaseInit                   ,
    getTypeInfoBaseInit                     ,
    setTypeInfoBaseInit                     ,
#if ENABLE_OVERLOADING
    typeInfo_baseInit                       ,
#endif


-- ** classData #attr:classData#
{- | User-supplied data passed to the class init\/finalize functions
-}
    clearTypeInfoClassData                  ,
    getTypeInfoClassData                    ,
    setTypeInfoClassData                    ,
#if ENABLE_OVERLOADING
    typeInfo_classData                      ,
#endif


-- ** classFinalize #attr:classFinalize#
{- | Location of the class finalization function for
 classed and instantiatable types. Location of the default vtable
 finalization function for interface types. (optional)
-}
    clearTypeInfoClassFinalize              ,
    getTypeInfoClassFinalize                ,
    setTypeInfoClassFinalize                ,
#if ENABLE_OVERLOADING
    typeInfo_classFinalize                  ,
#endif


-- ** classInit #attr:classInit#
{- | Location of the class initialization function for
 classed and instantiatable types. Location of the default vtable
 inititalization function for interface types. (optional) This function
 is used both to fill in virtual functions in the class or default vtable,
 and to do type-specific setup such as registering signals and object
 properties.
-}
    clearTypeInfoClassInit                  ,
    getTypeInfoClassInit                    ,
    setTypeInfoClassInit                    ,
#if ENABLE_OVERLOADING
    typeInfo_classInit                      ,
#endif


-- ** classSize #attr:classSize#
{- | Size of the class structure (required for interface, classed and instantiatable types)
-}
    getTypeInfoClassSize                    ,
    setTypeInfoClassSize                    ,
#if ENABLE_OVERLOADING
    typeInfo_classSize                      ,
#endif


-- ** instanceInit #attr:instanceInit#
{- | Location of the instance initialization function (optional, for instantiatable types only)
-}
    clearTypeInfoInstanceInit               ,
    getTypeInfoInstanceInit                 ,
    setTypeInfoInstanceInit                 ,
#if ENABLE_OVERLOADING
    typeInfo_instanceInit                   ,
#endif


-- ** instanceSize #attr:instanceSize#
{- | Size of the instance (object) structure (required for instantiatable types only)
-}
    getTypeInfoInstanceSize                 ,
    setTypeInfoInstanceSize                 ,
#if ENABLE_OVERLOADING
    typeInfo_instanceSize                   ,
#endif


-- ** nPreallocs #attr:nPreallocs#
{- | Prior to GLib 2.10, it specified the number of pre-allocated (cached) instances to reserve memory for (0 indicates no caching). Since GLib 2.10, it is ignored, since instances are allocated with the [slice allocator][glib-Memory-Slices] now.
-}
    getTypeInfoNPreallocs                   ,
    setTypeInfoNPreallocs                   ,
#if ENABLE_OVERLOADING
    typeInfo_nPreallocs                     ,
#endif


-- ** valueTable #attr:valueTable#
{- | A 'GI.GObject.Structs.TypeValueTable.TypeValueTable' function table for generic handling of GValues
 of this type (usually only useful for fundamental types)
-}
    clearTypeInfoValueTable                 ,
    getTypeInfoValueTable                   ,
    setTypeInfoValueTable                   ,
#if ENABLE_OVERLOADING
    typeInfo_valueTable                     ,
#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.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
import {-# SOURCE #-} qualified GI.GObject.Structs.TypeValueTable as GObject.TypeValueTable

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

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `TypeInfo`.
noTypeInfo :: Maybe TypeInfo
noTypeInfo = Nothing

{- |
Get the value of the “@class_size@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' typeInfo #classSize
@
-}
getTypeInfoClassSize :: MonadIO m => TypeInfo -> m Word16
getTypeInfoClassSize s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO Word16
    return val

{- |
Set the value of the “@class_size@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' typeInfo [ #classSize 'Data.GI.Base.Attributes.:=' value ]
@
-}
setTypeInfoClassSize :: MonadIO m => TypeInfo -> Word16 -> m ()
setTypeInfoClassSize s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: Word16)

#if ENABLE_OVERLOADING
data TypeInfoClassSizeFieldInfo
instance AttrInfo TypeInfoClassSizeFieldInfo where
    type AttrAllowedOps TypeInfoClassSizeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TypeInfoClassSizeFieldInfo = (~) Word16
    type AttrBaseTypeConstraint TypeInfoClassSizeFieldInfo = (~) TypeInfo
    type AttrGetType TypeInfoClassSizeFieldInfo = Word16
    type AttrLabel TypeInfoClassSizeFieldInfo = "class_size"
    type AttrOrigin TypeInfoClassSizeFieldInfo = TypeInfo
    attrGet _ = getTypeInfoClassSize
    attrSet _ = setTypeInfoClassSize
    attrConstruct = undefined
    attrClear _ = undefined

typeInfo_classSize :: AttrLabelProxy "classSize"
typeInfo_classSize = AttrLabelProxy

#endif


{- |
Get the value of the “@base_init@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' typeInfo #baseInit
@
-}
getTypeInfoBaseInit :: MonadIO m => TypeInfo -> m (Maybe GObject.Callbacks.BaseInitFunc)
getTypeInfoBaseInit s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO (FunPtr GObject.Callbacks.C_BaseInitFunc)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = GObject.Callbacks.dynamic_BaseInitFunc val'
        return val''
    return result

{- |
Set the value of the “@base_init@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' typeInfo [ #baseInit 'Data.GI.Base.Attributes.:=' value ]
@
-}
setTypeInfoBaseInit :: MonadIO m => TypeInfo -> FunPtr GObject.Callbacks.C_BaseInitFunc -> m ()
setTypeInfoBaseInit s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (val :: FunPtr GObject.Callbacks.C_BaseInitFunc)

{- |
Set the value of the “@base_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' #baseInit
@
-}
clearTypeInfoBaseInit :: MonadIO m => TypeInfo -> m ()
clearTypeInfoBaseInit s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullFunPtr :: FunPtr GObject.Callbacks.C_BaseInitFunc)

#if ENABLE_OVERLOADING
data TypeInfoBaseInitFieldInfo
instance AttrInfo TypeInfoBaseInitFieldInfo where
    type AttrAllowedOps TypeInfoBaseInitFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TypeInfoBaseInitFieldInfo = (~) (FunPtr GObject.Callbacks.C_BaseInitFunc)
    type AttrBaseTypeConstraint TypeInfoBaseInitFieldInfo = (~) TypeInfo
    type AttrGetType TypeInfoBaseInitFieldInfo = Maybe GObject.Callbacks.BaseInitFunc
    type AttrLabel TypeInfoBaseInitFieldInfo = "base_init"
    type AttrOrigin TypeInfoBaseInitFieldInfo = TypeInfo
    attrGet _ = getTypeInfoBaseInit
    attrSet _ = setTypeInfoBaseInit
    attrConstruct = undefined
    attrClear _ = clearTypeInfoBaseInit

typeInfo_baseInit :: AttrLabelProxy "baseInit"
typeInfo_baseInit = AttrLabelProxy

#endif


{- |
Get the value of the “@base_finalize@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' typeInfo #baseFinalize
@
-}
getTypeInfoBaseFinalize :: MonadIO m => TypeInfo -> m (Maybe GObject.Callbacks.BaseFinalizeFunc)
getTypeInfoBaseFinalize s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO (FunPtr GObject.Callbacks.C_BaseFinalizeFunc)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = GObject.Callbacks.dynamic_BaseFinalizeFunc val'
        return val''
    return result

{- |
Set the value of the “@base_finalize@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' typeInfo [ #baseFinalize 'Data.GI.Base.Attributes.:=' value ]
@
-}
setTypeInfoBaseFinalize :: MonadIO m => TypeInfo -> FunPtr GObject.Callbacks.C_BaseFinalizeFunc -> m ()
setTypeInfoBaseFinalize s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (val :: FunPtr GObject.Callbacks.C_BaseFinalizeFunc)

{- |
Set the value of the “@base_finalize@” 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' #baseFinalize
@
-}
clearTypeInfoBaseFinalize :: MonadIO m => TypeInfo -> m ()
clearTypeInfoBaseFinalize s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (FP.nullFunPtr :: FunPtr GObject.Callbacks.C_BaseFinalizeFunc)

#if ENABLE_OVERLOADING
data TypeInfoBaseFinalizeFieldInfo
instance AttrInfo TypeInfoBaseFinalizeFieldInfo where
    type AttrAllowedOps TypeInfoBaseFinalizeFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TypeInfoBaseFinalizeFieldInfo = (~) (FunPtr GObject.Callbacks.C_BaseFinalizeFunc)
    type AttrBaseTypeConstraint TypeInfoBaseFinalizeFieldInfo = (~) TypeInfo
    type AttrGetType TypeInfoBaseFinalizeFieldInfo = Maybe GObject.Callbacks.BaseFinalizeFunc
    type AttrLabel TypeInfoBaseFinalizeFieldInfo = "base_finalize"
    type AttrOrigin TypeInfoBaseFinalizeFieldInfo = TypeInfo
    attrGet _ = getTypeInfoBaseFinalize
    attrSet _ = setTypeInfoBaseFinalize
    attrConstruct = undefined
    attrClear _ = clearTypeInfoBaseFinalize

typeInfo_baseFinalize :: AttrLabelProxy "baseFinalize"
typeInfo_baseFinalize = AttrLabelProxy

#endif


{- |
Get the value of the “@class_init@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' typeInfo #classInit
@
-}
getTypeInfoClassInit :: MonadIO m => TypeInfo -> m (Maybe GObject.Callbacks.ClassInitFunc)
getTypeInfoClassInit s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO (FunPtr GObject.Callbacks.C_ClassInitFunc)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = GObject.Callbacks.dynamic_ClassInitFunc val'
        return val''
    return result

{- |
Set the value of the “@class_init@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' typeInfo [ #classInit 'Data.GI.Base.Attributes.:=' value ]
@
-}
setTypeInfoClassInit :: MonadIO m => TypeInfo -> FunPtr GObject.Callbacks.C_ClassInitFunc -> m ()
setTypeInfoClassInit s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (val :: FunPtr GObject.Callbacks.C_ClassInitFunc)

{- |
Set the value of the “@class_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' #classInit
@
-}
clearTypeInfoClassInit :: MonadIO m => TypeInfo -> m ()
clearTypeInfoClassInit s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (FP.nullFunPtr :: FunPtr GObject.Callbacks.C_ClassInitFunc)

#if ENABLE_OVERLOADING
data TypeInfoClassInitFieldInfo
instance AttrInfo TypeInfoClassInitFieldInfo where
    type AttrAllowedOps TypeInfoClassInitFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TypeInfoClassInitFieldInfo = (~) (FunPtr GObject.Callbacks.C_ClassInitFunc)
    type AttrBaseTypeConstraint TypeInfoClassInitFieldInfo = (~) TypeInfo
    type AttrGetType TypeInfoClassInitFieldInfo = Maybe GObject.Callbacks.ClassInitFunc
    type AttrLabel TypeInfoClassInitFieldInfo = "class_init"
    type AttrOrigin TypeInfoClassInitFieldInfo = TypeInfo
    attrGet _ = getTypeInfoClassInit
    attrSet _ = setTypeInfoClassInit
    attrConstruct = undefined
    attrClear _ = clearTypeInfoClassInit

typeInfo_classInit :: AttrLabelProxy "classInit"
typeInfo_classInit = AttrLabelProxy

#endif


{- |
Get the value of the “@class_finalize@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' typeInfo #classFinalize
@
-}
getTypeInfoClassFinalize :: MonadIO m => TypeInfo -> m (Maybe GObject.Callbacks.ClassFinalizeFunc)
getTypeInfoClassFinalize s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 32) :: IO (FunPtr GObject.Callbacks.C_ClassFinalizeFunc)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = GObject.Callbacks.dynamic_ClassFinalizeFunc val'
        return val''
    return result

{- |
Set the value of the “@class_finalize@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' typeInfo [ #classFinalize 'Data.GI.Base.Attributes.:=' value ]
@
-}
setTypeInfoClassFinalize :: MonadIO m => TypeInfo -> FunPtr GObject.Callbacks.C_ClassFinalizeFunc -> m ()
setTypeInfoClassFinalize s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 32) (val :: FunPtr GObject.Callbacks.C_ClassFinalizeFunc)

{- |
Set the value of the “@class_finalize@” 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' #classFinalize
@
-}
clearTypeInfoClassFinalize :: MonadIO m => TypeInfo -> m ()
clearTypeInfoClassFinalize s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 32) (FP.nullFunPtr :: FunPtr GObject.Callbacks.C_ClassFinalizeFunc)

#if ENABLE_OVERLOADING
data TypeInfoClassFinalizeFieldInfo
instance AttrInfo TypeInfoClassFinalizeFieldInfo where
    type AttrAllowedOps TypeInfoClassFinalizeFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TypeInfoClassFinalizeFieldInfo = (~) (FunPtr GObject.Callbacks.C_ClassFinalizeFunc)
    type AttrBaseTypeConstraint TypeInfoClassFinalizeFieldInfo = (~) TypeInfo
    type AttrGetType TypeInfoClassFinalizeFieldInfo = Maybe GObject.Callbacks.ClassFinalizeFunc
    type AttrLabel TypeInfoClassFinalizeFieldInfo = "class_finalize"
    type AttrOrigin TypeInfoClassFinalizeFieldInfo = TypeInfo
    attrGet _ = getTypeInfoClassFinalize
    attrSet _ = setTypeInfoClassFinalize
    attrConstruct = undefined
    attrClear _ = clearTypeInfoClassFinalize

typeInfo_classFinalize :: AttrLabelProxy "classFinalize"
typeInfo_classFinalize = AttrLabelProxy

#endif


{- |
Get the value of the “@class_data@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' typeInfo #classData
@
-}
getTypeInfoClassData :: MonadIO m => TypeInfo -> m (Ptr ())
getTypeInfoClassData s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 40) :: IO (Ptr ())
    return val

{- |
Set the value of the “@class_data@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' typeInfo [ #classData 'Data.GI.Base.Attributes.:=' value ]
@
-}
setTypeInfoClassData :: MonadIO m => TypeInfo -> Ptr () -> m ()
setTypeInfoClassData s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 40) (val :: Ptr ())

{- |
Set the value of the “@class_data@” 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' #classData
@
-}
clearTypeInfoClassData :: MonadIO m => TypeInfo -> m ()
clearTypeInfoClassData s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 40) (FP.nullPtr :: Ptr ())

#if ENABLE_OVERLOADING
data TypeInfoClassDataFieldInfo
instance AttrInfo TypeInfoClassDataFieldInfo where
    type AttrAllowedOps TypeInfoClassDataFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TypeInfoClassDataFieldInfo = (~) (Ptr ())
    type AttrBaseTypeConstraint TypeInfoClassDataFieldInfo = (~) TypeInfo
    type AttrGetType TypeInfoClassDataFieldInfo = Ptr ()
    type AttrLabel TypeInfoClassDataFieldInfo = "class_data"
    type AttrOrigin TypeInfoClassDataFieldInfo = TypeInfo
    attrGet _ = getTypeInfoClassData
    attrSet _ = setTypeInfoClassData
    attrConstruct = undefined
    attrClear _ = clearTypeInfoClassData

typeInfo_classData :: AttrLabelProxy "classData"
typeInfo_classData = AttrLabelProxy

#endif


{- |
Get the value of the “@instance_size@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' typeInfo #instanceSize
@
-}
getTypeInfoInstanceSize :: MonadIO m => TypeInfo -> m Word16
getTypeInfoInstanceSize s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 48) :: IO Word16
    return val

{- |
Set the value of the “@instance_size@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' typeInfo [ #instanceSize 'Data.GI.Base.Attributes.:=' value ]
@
-}
setTypeInfoInstanceSize :: MonadIO m => TypeInfo -> Word16 -> m ()
setTypeInfoInstanceSize s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 48) (val :: Word16)

#if ENABLE_OVERLOADING
data TypeInfoInstanceSizeFieldInfo
instance AttrInfo TypeInfoInstanceSizeFieldInfo where
    type AttrAllowedOps TypeInfoInstanceSizeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TypeInfoInstanceSizeFieldInfo = (~) Word16
    type AttrBaseTypeConstraint TypeInfoInstanceSizeFieldInfo = (~) TypeInfo
    type AttrGetType TypeInfoInstanceSizeFieldInfo = Word16
    type AttrLabel TypeInfoInstanceSizeFieldInfo = "instance_size"
    type AttrOrigin TypeInfoInstanceSizeFieldInfo = TypeInfo
    attrGet _ = getTypeInfoInstanceSize
    attrSet _ = setTypeInfoInstanceSize
    attrConstruct = undefined
    attrClear _ = undefined

typeInfo_instanceSize :: AttrLabelProxy "instanceSize"
typeInfo_instanceSize = AttrLabelProxy

#endif


{- |
Get the value of the “@n_preallocs@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' typeInfo #nPreallocs
@
-}
getTypeInfoNPreallocs :: MonadIO m => TypeInfo -> m Word16
getTypeInfoNPreallocs s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 50) :: IO Word16
    return val

{- |
Set the value of the “@n_preallocs@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' typeInfo [ #nPreallocs 'Data.GI.Base.Attributes.:=' value ]
@
-}
setTypeInfoNPreallocs :: MonadIO m => TypeInfo -> Word16 -> m ()
setTypeInfoNPreallocs s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 50) (val :: Word16)

#if ENABLE_OVERLOADING
data TypeInfoNPreallocsFieldInfo
instance AttrInfo TypeInfoNPreallocsFieldInfo where
    type AttrAllowedOps TypeInfoNPreallocsFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TypeInfoNPreallocsFieldInfo = (~) Word16
    type AttrBaseTypeConstraint TypeInfoNPreallocsFieldInfo = (~) TypeInfo
    type AttrGetType TypeInfoNPreallocsFieldInfo = Word16
    type AttrLabel TypeInfoNPreallocsFieldInfo = "n_preallocs"
    type AttrOrigin TypeInfoNPreallocsFieldInfo = TypeInfo
    attrGet _ = getTypeInfoNPreallocs
    attrSet _ = setTypeInfoNPreallocs
    attrConstruct = undefined
    attrClear _ = undefined

typeInfo_nPreallocs :: AttrLabelProxy "nPreallocs"
typeInfo_nPreallocs = AttrLabelProxy

#endif


{- |
Get the value of the “@instance_init@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' typeInfo #instanceInit
@
-}
getTypeInfoInstanceInit :: MonadIO m => TypeInfo -> m (Maybe GObject.Callbacks.InstanceInitFunc)
getTypeInfoInstanceInit s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 56) :: IO (FunPtr GObject.Callbacks.C_InstanceInitFunc)
    result <- SP.convertFunPtrIfNonNull val $ \val' -> do
        let val'' = GObject.Callbacks.dynamic_InstanceInitFunc val'
        return val''
    return result

{- |
Set the value of the “@instance_init@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' typeInfo [ #instanceInit 'Data.GI.Base.Attributes.:=' value ]
@
-}
setTypeInfoInstanceInit :: MonadIO m => TypeInfo -> FunPtr GObject.Callbacks.C_InstanceInitFunc -> m ()
setTypeInfoInstanceInit s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 56) (val :: FunPtr GObject.Callbacks.C_InstanceInitFunc)

{- |
Set the value of the “@instance_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' #instanceInit
@
-}
clearTypeInfoInstanceInit :: MonadIO m => TypeInfo -> m ()
clearTypeInfoInstanceInit s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 56) (FP.nullFunPtr :: FunPtr GObject.Callbacks.C_InstanceInitFunc)

#if ENABLE_OVERLOADING
data TypeInfoInstanceInitFieldInfo
instance AttrInfo TypeInfoInstanceInitFieldInfo where
    type AttrAllowedOps TypeInfoInstanceInitFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TypeInfoInstanceInitFieldInfo = (~) (FunPtr GObject.Callbacks.C_InstanceInitFunc)
    type AttrBaseTypeConstraint TypeInfoInstanceInitFieldInfo = (~) TypeInfo
    type AttrGetType TypeInfoInstanceInitFieldInfo = Maybe GObject.Callbacks.InstanceInitFunc
    type AttrLabel TypeInfoInstanceInitFieldInfo = "instance_init"
    type AttrOrigin TypeInfoInstanceInitFieldInfo = TypeInfo
    attrGet _ = getTypeInfoInstanceInit
    attrSet _ = setTypeInfoInstanceInit
    attrConstruct = undefined
    attrClear _ = clearTypeInfoInstanceInit

typeInfo_instanceInit :: AttrLabelProxy "instanceInit"
typeInfo_instanceInit = AttrLabelProxy

#endif


{- |
Get the value of the “@value_table@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' typeInfo #valueTable
@
-}
getTypeInfoValueTable :: MonadIO m => TypeInfo -> m (Maybe GObject.TypeValueTable.TypeValueTable)
getTypeInfoValueTable s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 64) :: IO (Ptr GObject.TypeValueTable.TypeValueTable)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newPtr GObject.TypeValueTable.TypeValueTable) val'
        return val''
    return result

{- |
Set the value of the “@value_table@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' typeInfo [ #valueTable 'Data.GI.Base.Attributes.:=' value ]
@
-}
setTypeInfoValueTable :: MonadIO m => TypeInfo -> Ptr GObject.TypeValueTable.TypeValueTable -> m ()
setTypeInfoValueTable s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 64) (val :: Ptr GObject.TypeValueTable.TypeValueTable)

{- |
Set the value of the “@value_table@” 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' #valueTable
@
-}
clearTypeInfoValueTable :: MonadIO m => TypeInfo -> m ()
clearTypeInfoValueTable s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 64) (FP.nullPtr :: Ptr GObject.TypeValueTable.TypeValueTable)

#if ENABLE_OVERLOADING
data TypeInfoValueTableFieldInfo
instance AttrInfo TypeInfoValueTableFieldInfo where
    type AttrAllowedOps TypeInfoValueTableFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TypeInfoValueTableFieldInfo = (~) (Ptr GObject.TypeValueTable.TypeValueTable)
    type AttrBaseTypeConstraint TypeInfoValueTableFieldInfo = (~) TypeInfo
    type AttrGetType TypeInfoValueTableFieldInfo = Maybe GObject.TypeValueTable.TypeValueTable
    type AttrLabel TypeInfoValueTableFieldInfo = "value_table"
    type AttrOrigin TypeInfoValueTableFieldInfo = TypeInfo
    attrGet _ = getTypeInfoValueTable
    attrSet _ = setTypeInfoValueTable
    attrConstruct = undefined
    attrClear _ = clearTypeInfoValueTable

typeInfo_valueTable :: AttrLabelProxy "valueTable"
typeInfo_valueTable = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList TypeInfo
type instance O.AttributeList TypeInfo = TypeInfoAttributeList
type TypeInfoAttributeList = ('[ '("classSize", TypeInfoClassSizeFieldInfo), '("baseInit", TypeInfoBaseInitFieldInfo), '("baseFinalize", TypeInfoBaseFinalizeFieldInfo), '("classInit", TypeInfoClassInitFieldInfo), '("classFinalize", TypeInfoClassFinalizeFieldInfo), '("classData", TypeInfoClassDataFieldInfo), '("instanceSize", TypeInfoInstanceSizeFieldInfo), '("nPreallocs", TypeInfoNPreallocsFieldInfo), '("instanceInit", TypeInfoInstanceInitFieldInfo), '("valueTable", TypeInfoValueTableFieldInfo)] :: [(Symbol, *)])
#endif

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

instance (info ~ ResolveTypeInfoMethod t TypeInfo, O.MethodInfo info TypeInfo p) => OL.IsLabel t (TypeInfo -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#else
    fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif

#endif