{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- 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 t'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'.

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

module GI.GObject.Structs.TypeInfo
    ( 

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


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveTypeInfoMethod                   ,
#endif



 -- * Properties


-- ** baseFinalize #attr:baseFinalize#
-- | Location of the base finalization function (optional)

    clearTypeInfoBaseFinalize               ,
    getTypeInfoBaseFinalize                 ,
    setTypeInfoBaseFinalize                 ,
#if defined(ENABLE_OVERLOADING)
    typeInfo_baseFinalize                   ,
#endif


-- ** baseInit #attr:baseInit#
-- | Location of the base initialization function (optional)

    clearTypeInfoBaseInit                   ,
    getTypeInfoBaseInit                     ,
    setTypeInfoBaseInit                     ,
#if defined(ENABLE_OVERLOADING)
    typeInfo_baseInit                       ,
#endif


-- ** classData #attr:classData#
-- | User-supplied data passed to the class init\/finalize functions

    clearTypeInfoClassData                  ,
    getTypeInfoClassData                    ,
    setTypeInfoClassData                    ,
#if defined(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 defined(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 defined(ENABLE_OVERLOADING)
    typeInfo_classInit                      ,
#endif


-- ** classSize #attr:classSize#
-- | Size of the class structure (required for interface, classed and instantiatable types)

    getTypeInfoClassSize                    ,
    setTypeInfoClassSize                    ,
#if defined(ENABLE_OVERLOADING)
    typeInfo_classSize                      ,
#endif


-- ** instanceInit #attr:instanceInit#
-- | Location of the instance initialization function (optional, for instantiatable types only)

    clearTypeInfoInstanceInit               ,
    getTypeInfoInstanceInit                 ,
    setTypeInfoInstanceInit                 ,
#if defined(ENABLE_OVERLOADING)
    typeInfo_instanceInit                   ,
#endif


-- ** instanceSize #attr:instanceSize#
-- | Size of the instance (object) structure (required for instantiatable types only)

    getTypeInfoInstanceSize                 ,
    setTypeInfoInstanceSize                 ,
#if defined(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 defined(ENABLE_OVERLOADING)
    typeInfo_nPreallocs                     ,
#endif


-- ** valueTable #attr:valueTable#
-- | A t'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 defined(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.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.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.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 GHC.Records as R

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 (SP.ManagedPtr TypeInfo)
    deriving (TypeInfo -> TypeInfo -> Bool
(TypeInfo -> TypeInfo -> Bool)
-> (TypeInfo -> TypeInfo -> Bool) -> Eq TypeInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeInfo -> TypeInfo -> Bool
$c/= :: TypeInfo -> TypeInfo -> Bool
== :: TypeInfo -> TypeInfo -> Bool
$c== :: TypeInfo -> TypeInfo -> Bool
Eq)

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

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


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

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


-- | 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 :: forall (m :: * -> *). MonadIO m => TypeInfo -> m Word16
getTypeInfoClassSize TypeInfo
s = IO Word16 -> m Word16
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word16 -> m Word16) -> IO Word16 -> m Word16
forall a b. (a -> b) -> a -> b
$ TypeInfo -> (Ptr TypeInfo -> IO Word16) -> IO Word16
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO Word16) -> IO Word16)
-> (Ptr TypeInfo -> IO Word16) -> IO Word16
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    Word16
val <- Ptr Word16 -> IO Word16
forall a. Storable a => Ptr a -> IO a
peek (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO Word16
    Word16 -> IO Word16
forall (m :: * -> *) a. Monad m => a -> m a
return Word16
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 :: forall (m :: * -> *). MonadIO m => TypeInfo -> Word16 -> m ()
setTypeInfoClassSize TypeInfo
s Word16
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TypeInfo -> (Ptr TypeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO ()) -> IO ())
-> (Ptr TypeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    Ptr Word16 -> Word16 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Word16
val :: Word16)

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

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 :: forall (m :: * -> *).
MonadIO m =>
TypeInfo -> m (Maybe BaseInitFunc)
getTypeInfoBaseInit TypeInfo
s = IO (Maybe BaseInitFunc) -> m (Maybe BaseInitFunc)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe BaseInitFunc) -> m (Maybe BaseInitFunc))
-> IO (Maybe BaseInitFunc) -> m (Maybe BaseInitFunc)
forall a b. (a -> b) -> a -> b
$ TypeInfo
-> (Ptr TypeInfo -> IO (Maybe BaseInitFunc))
-> IO (Maybe BaseInitFunc)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO (Maybe BaseInitFunc))
 -> IO (Maybe BaseInitFunc))
-> (Ptr TypeInfo -> IO (Maybe BaseInitFunc))
-> IO (Maybe BaseInitFunc)
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    FunPtr C_BaseInitFunc
val <- Ptr (FunPtr C_BaseInitFunc) -> IO (FunPtr C_BaseInitFunc)
forall a. Storable a => Ptr a -> IO a
peek (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr (FunPtr C_BaseInitFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO (FunPtr GObject.Callbacks.C_BaseInitFunc)
    Maybe BaseInitFunc
result <- FunPtr C_BaseInitFunc
-> (FunPtr C_BaseInitFunc -> IO BaseInitFunc)
-> IO (Maybe BaseInitFunc)
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr C_BaseInitFunc
val ((FunPtr C_BaseInitFunc -> IO BaseInitFunc)
 -> IO (Maybe BaseInitFunc))
-> (FunPtr C_BaseInitFunc -> IO BaseInitFunc)
-> IO (Maybe BaseInitFunc)
forall a b. (a -> b) -> a -> b
$ \FunPtr C_BaseInitFunc
val' -> do
        let val'' :: BaseInitFunc
val'' = FunPtr C_BaseInitFunc -> BaseInitFunc
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_BaseInitFunc -> TypeClass -> m ()
GObject.Callbacks.dynamic_BaseInitFunc FunPtr C_BaseInitFunc
val'
        BaseInitFunc -> IO BaseInitFunc
forall (m :: * -> *) a. Monad m => a -> m a
return BaseInitFunc
val''
    Maybe BaseInitFunc -> IO (Maybe BaseInitFunc)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe BaseInitFunc
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 :: forall (m :: * -> *).
MonadIO m =>
TypeInfo -> FunPtr C_BaseInitFunc -> m ()
setTypeInfoBaseInit TypeInfo
s FunPtr C_BaseInitFunc
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TypeInfo -> (Ptr TypeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO ()) -> IO ())
-> (Ptr TypeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    Ptr (FunPtr C_BaseInitFunc) -> FunPtr C_BaseInitFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr (FunPtr C_BaseInitFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (FunPtr C_BaseInitFunc
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 :: forall (m :: * -> *). MonadIO m => TypeInfo -> m ()
clearTypeInfoBaseInit TypeInfo
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TypeInfo -> (Ptr TypeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO ()) -> IO ())
-> (Ptr TypeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    Ptr (FunPtr C_BaseInitFunc) -> FunPtr C_BaseInitFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr (FunPtr C_BaseInitFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (FunPtr C_BaseInitFunc
forall a. FunPtr a
FP.nullFunPtr :: FunPtr GObject.Callbacks.C_BaseInitFunc)

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

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 :: forall (m :: * -> *).
MonadIO m =>
TypeInfo -> m (Maybe BaseInitFunc)
getTypeInfoBaseFinalize TypeInfo
s = IO (Maybe BaseInitFunc) -> m (Maybe BaseInitFunc)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe BaseInitFunc) -> m (Maybe BaseInitFunc))
-> IO (Maybe BaseInitFunc) -> m (Maybe BaseInitFunc)
forall a b. (a -> b) -> a -> b
$ TypeInfo
-> (Ptr TypeInfo -> IO (Maybe BaseInitFunc))
-> IO (Maybe BaseInitFunc)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO (Maybe BaseInitFunc))
 -> IO (Maybe BaseInitFunc))
-> (Ptr TypeInfo -> IO (Maybe BaseInitFunc))
-> IO (Maybe BaseInitFunc)
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    FunPtr C_BaseInitFunc
val <- Ptr (FunPtr C_BaseInitFunc) -> IO (FunPtr C_BaseInitFunc)
forall a. Storable a => Ptr a -> IO a
peek (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr (FunPtr C_BaseInitFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO (FunPtr GObject.Callbacks.C_BaseFinalizeFunc)
    Maybe BaseInitFunc
result <- FunPtr C_BaseInitFunc
-> (FunPtr C_BaseInitFunc -> IO BaseInitFunc)
-> IO (Maybe BaseInitFunc)
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr C_BaseInitFunc
val ((FunPtr C_BaseInitFunc -> IO BaseInitFunc)
 -> IO (Maybe BaseInitFunc))
-> (FunPtr C_BaseInitFunc -> IO BaseInitFunc)
-> IO (Maybe BaseInitFunc)
forall a b. (a -> b) -> a -> b
$ \FunPtr C_BaseInitFunc
val' -> do
        let val'' :: BaseInitFunc
val'' = FunPtr C_BaseInitFunc -> BaseInitFunc
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_BaseInitFunc -> TypeClass -> m ()
GObject.Callbacks.dynamic_BaseFinalizeFunc FunPtr C_BaseInitFunc
val'
        BaseInitFunc -> IO BaseInitFunc
forall (m :: * -> *) a. Monad m => a -> m a
return BaseInitFunc
val''
    Maybe BaseInitFunc -> IO (Maybe BaseInitFunc)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe BaseInitFunc
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 :: forall (m :: * -> *).
MonadIO m =>
TypeInfo -> FunPtr C_BaseInitFunc -> m ()
setTypeInfoBaseFinalize TypeInfo
s FunPtr C_BaseInitFunc
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TypeInfo -> (Ptr TypeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO ()) -> IO ())
-> (Ptr TypeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    Ptr (FunPtr C_BaseInitFunc) -> FunPtr C_BaseInitFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr (FunPtr C_BaseInitFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (FunPtr C_BaseInitFunc
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 :: forall (m :: * -> *). MonadIO m => TypeInfo -> m ()
clearTypeInfoBaseFinalize TypeInfo
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TypeInfo -> (Ptr TypeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO ()) -> IO ())
-> (Ptr TypeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    Ptr (FunPtr C_BaseInitFunc) -> FunPtr C_BaseInitFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr (FunPtr C_BaseInitFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (FunPtr C_BaseInitFunc
forall a. FunPtr a
FP.nullFunPtr :: FunPtr GObject.Callbacks.C_BaseFinalizeFunc)

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

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 :: forall (m :: * -> *).
MonadIO m =>
TypeInfo -> m (Maybe ClassInitFunc)
getTypeInfoClassInit TypeInfo
s = IO (Maybe ClassInitFunc) -> m (Maybe ClassInitFunc)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ClassInitFunc) -> m (Maybe ClassInitFunc))
-> IO (Maybe ClassInitFunc) -> m (Maybe ClassInitFunc)
forall a b. (a -> b) -> a -> b
$ TypeInfo
-> (Ptr TypeInfo -> IO (Maybe ClassInitFunc))
-> IO (Maybe ClassInitFunc)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO (Maybe ClassInitFunc))
 -> IO (Maybe ClassInitFunc))
-> (Ptr TypeInfo -> IO (Maybe ClassInitFunc))
-> IO (Maybe ClassInitFunc)
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    FunPtr C_ClassInitFunc
val <- Ptr (FunPtr C_ClassInitFunc) -> IO (FunPtr C_ClassInitFunc)
forall a. Storable a => Ptr a -> IO a
peek (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr (FunPtr C_ClassInitFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) :: IO (FunPtr GObject.Callbacks.C_ClassInitFunc)
    Maybe ClassInitFunc
result <- FunPtr C_ClassInitFunc
-> (FunPtr C_ClassInitFunc -> IO ClassInitFunc)
-> IO (Maybe ClassInitFunc)
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr C_ClassInitFunc
val ((FunPtr C_ClassInitFunc -> IO ClassInitFunc)
 -> IO (Maybe ClassInitFunc))
-> (FunPtr C_ClassInitFunc -> IO ClassInitFunc)
-> IO (Maybe ClassInitFunc)
forall a b. (a -> b) -> a -> b
$ \FunPtr C_ClassInitFunc
val' -> do
        let val'' :: ClassInitFunc
val'' = FunPtr C_ClassInitFunc -> ClassInitFunc
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_ClassInitFunc -> TypeClass -> Ptr () -> m ()
GObject.Callbacks.dynamic_ClassInitFunc FunPtr C_ClassInitFunc
val'
        ClassInitFunc -> IO ClassInitFunc
forall (m :: * -> *) a. Monad m => a -> m a
return ClassInitFunc
val''
    Maybe ClassInitFunc -> IO (Maybe ClassInitFunc)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ClassInitFunc
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 :: forall (m :: * -> *).
MonadIO m =>
TypeInfo -> FunPtr C_ClassInitFunc -> m ()
setTypeInfoClassInit TypeInfo
s FunPtr C_ClassInitFunc
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TypeInfo -> (Ptr TypeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO ()) -> IO ())
-> (Ptr TypeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    Ptr (FunPtr C_ClassInitFunc) -> FunPtr C_ClassInitFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr (FunPtr C_ClassInitFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (FunPtr C_ClassInitFunc
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 :: forall (m :: * -> *). MonadIO m => TypeInfo -> m ()
clearTypeInfoClassInit TypeInfo
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TypeInfo -> (Ptr TypeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO ()) -> IO ())
-> (Ptr TypeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    Ptr (FunPtr C_ClassInitFunc) -> FunPtr C_ClassInitFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr (FunPtr C_ClassInitFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (FunPtr C_ClassInitFunc
forall a. FunPtr a
FP.nullFunPtr :: FunPtr GObject.Callbacks.C_ClassInitFunc)

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

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 :: forall (m :: * -> *).
MonadIO m =>
TypeInfo -> m (Maybe ClassInitFunc)
getTypeInfoClassFinalize TypeInfo
s = IO (Maybe ClassInitFunc) -> m (Maybe ClassInitFunc)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ClassInitFunc) -> m (Maybe ClassInitFunc))
-> IO (Maybe ClassInitFunc) -> m (Maybe ClassInitFunc)
forall a b. (a -> b) -> a -> b
$ TypeInfo
-> (Ptr TypeInfo -> IO (Maybe ClassInitFunc))
-> IO (Maybe ClassInitFunc)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO (Maybe ClassInitFunc))
 -> IO (Maybe ClassInitFunc))
-> (Ptr TypeInfo -> IO (Maybe ClassInitFunc))
-> IO (Maybe ClassInitFunc)
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    FunPtr C_ClassInitFunc
val <- Ptr (FunPtr C_ClassInitFunc) -> IO (FunPtr C_ClassInitFunc)
forall a. Storable a => Ptr a -> IO a
peek (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr (FunPtr C_ClassInitFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) :: IO (FunPtr GObject.Callbacks.C_ClassFinalizeFunc)
    Maybe ClassInitFunc
result <- FunPtr C_ClassInitFunc
-> (FunPtr C_ClassInitFunc -> IO ClassInitFunc)
-> IO (Maybe ClassInitFunc)
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr C_ClassInitFunc
val ((FunPtr C_ClassInitFunc -> IO ClassInitFunc)
 -> IO (Maybe ClassInitFunc))
-> (FunPtr C_ClassInitFunc -> IO ClassInitFunc)
-> IO (Maybe ClassInitFunc)
forall a b. (a -> b) -> a -> b
$ \FunPtr C_ClassInitFunc
val' -> do
        let val'' :: ClassInitFunc
val'' = FunPtr C_ClassInitFunc -> ClassInitFunc
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_ClassInitFunc -> TypeClass -> Ptr () -> m ()
GObject.Callbacks.dynamic_ClassFinalizeFunc FunPtr C_ClassInitFunc
val'
        ClassInitFunc -> IO ClassInitFunc
forall (m :: * -> *) a. Monad m => a -> m a
return ClassInitFunc
val''
    Maybe ClassInitFunc -> IO (Maybe ClassInitFunc)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ClassInitFunc
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 :: forall (m :: * -> *).
MonadIO m =>
TypeInfo -> FunPtr C_ClassInitFunc -> m ()
setTypeInfoClassFinalize TypeInfo
s FunPtr C_ClassInitFunc
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TypeInfo -> (Ptr TypeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO ()) -> IO ())
-> (Ptr TypeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    Ptr (FunPtr C_ClassInitFunc) -> FunPtr C_ClassInitFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr (FunPtr C_ClassInitFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) (FunPtr C_ClassInitFunc
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 :: forall (m :: * -> *). MonadIO m => TypeInfo -> m ()
clearTypeInfoClassFinalize TypeInfo
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TypeInfo -> (Ptr TypeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO ()) -> IO ())
-> (Ptr TypeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    Ptr (FunPtr C_ClassInitFunc) -> FunPtr C_ClassInitFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr (FunPtr C_ClassInitFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) (FunPtr C_ClassInitFunc
forall a. FunPtr a
FP.nullFunPtr :: FunPtr GObject.Callbacks.C_ClassFinalizeFunc)

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

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 :: forall (m :: * -> *). MonadIO m => TypeInfo -> m (Ptr ())
getTypeInfoClassData TypeInfo
s = IO (Ptr ()) -> m (Ptr ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ TypeInfo -> (Ptr TypeInfo -> IO (Ptr ())) -> IO (Ptr ())
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO (Ptr ())) -> IO (Ptr ()))
-> (Ptr TypeInfo -> IO (Ptr ())) -> IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    Ptr ()
val <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40) :: IO (Ptr ())
    Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
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 :: forall (m :: * -> *). MonadIO m => TypeInfo -> Ptr () -> m ()
setTypeInfoClassData TypeInfo
s Ptr ()
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TypeInfo -> (Ptr TypeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO ()) -> IO ())
-> (Ptr TypeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40) (Ptr ()
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 :: forall (m :: * -> *). MonadIO m => TypeInfo -> m ()
clearTypeInfoClassData TypeInfo
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TypeInfo -> (Ptr TypeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO ()) -> IO ())
-> (Ptr TypeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40) (Ptr ()
forall a. Ptr a
FP.nullPtr :: Ptr ())

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

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 :: forall (m :: * -> *). MonadIO m => TypeInfo -> m Word16
getTypeInfoInstanceSize TypeInfo
s = IO Word16 -> m Word16
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word16 -> m Word16) -> IO Word16 -> m Word16
forall a b. (a -> b) -> a -> b
$ TypeInfo -> (Ptr TypeInfo -> IO Word16) -> IO Word16
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO Word16) -> IO Word16)
-> (Ptr TypeInfo -> IO Word16) -> IO Word16
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    Word16
val <- Ptr Word16 -> IO Word16
forall a. Storable a => Ptr a -> IO a
peek (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48) :: IO Word16
    Word16 -> IO Word16
forall (m :: * -> *) a. Monad m => a -> m a
return Word16
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 :: forall (m :: * -> *). MonadIO m => TypeInfo -> Word16 -> m ()
setTypeInfoInstanceSize TypeInfo
s Word16
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TypeInfo -> (Ptr TypeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO ()) -> IO ())
-> (Ptr TypeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    Ptr Word16 -> Word16 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48) (Word16
val :: Word16)

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

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 :: forall (m :: * -> *). MonadIO m => TypeInfo -> m Word16
getTypeInfoNPreallocs TypeInfo
s = IO Word16 -> m Word16
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word16 -> m Word16) -> IO Word16 -> m Word16
forall a b. (a -> b) -> a -> b
$ TypeInfo -> (Ptr TypeInfo -> IO Word16) -> IO Word16
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO Word16) -> IO Word16)
-> (Ptr TypeInfo -> IO Word16) -> IO Word16
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    Word16
val <- Ptr Word16 -> IO Word16
forall a. Storable a => Ptr a -> IO a
peek (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
50) :: IO Word16
    Word16 -> IO Word16
forall (m :: * -> *) a. Monad m => a -> m a
return Word16
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 :: forall (m :: * -> *). MonadIO m => TypeInfo -> Word16 -> m ()
setTypeInfoNPreallocs TypeInfo
s Word16
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TypeInfo -> (Ptr TypeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO ()) -> IO ())
-> (Ptr TypeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    Ptr Word16 -> Word16 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
50) (Word16
val :: Word16)

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

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 :: forall (m :: * -> *).
MonadIO m =>
TypeInfo -> m (Maybe InstanceInitFunc)
getTypeInfoInstanceInit TypeInfo
s = IO (Maybe InstanceInitFunc) -> m (Maybe InstanceInitFunc)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe InstanceInitFunc) -> m (Maybe InstanceInitFunc))
-> IO (Maybe InstanceInitFunc) -> m (Maybe InstanceInitFunc)
forall a b. (a -> b) -> a -> b
$ TypeInfo
-> (Ptr TypeInfo -> IO (Maybe InstanceInitFunc))
-> IO (Maybe InstanceInitFunc)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO (Maybe InstanceInitFunc))
 -> IO (Maybe InstanceInitFunc))
-> (Ptr TypeInfo -> IO (Maybe InstanceInitFunc))
-> IO (Maybe InstanceInitFunc)
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    FunPtr C_InstanceInitFunc
val <- Ptr (FunPtr C_InstanceInitFunc) -> IO (FunPtr C_InstanceInitFunc)
forall a. Storable a => Ptr a -> IO a
peek (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr (FunPtr C_InstanceInitFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56) :: IO (FunPtr GObject.Callbacks.C_InstanceInitFunc)
    Maybe InstanceInitFunc
result <- FunPtr C_InstanceInitFunc
-> (FunPtr C_InstanceInitFunc -> IO InstanceInitFunc)
-> IO (Maybe InstanceInitFunc)
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr C_InstanceInitFunc
val ((FunPtr C_InstanceInitFunc -> IO InstanceInitFunc)
 -> IO (Maybe InstanceInitFunc))
-> (FunPtr C_InstanceInitFunc -> IO InstanceInitFunc)
-> IO (Maybe InstanceInitFunc)
forall a b. (a -> b) -> a -> b
$ \FunPtr C_InstanceInitFunc
val' -> do
        let val'' :: InstanceInitFunc
val'' = FunPtr C_InstanceInitFunc -> InstanceInitFunc
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_InstanceInitFunc -> TypeInstance -> TypeClass -> m ()
GObject.Callbacks.dynamic_InstanceInitFunc FunPtr C_InstanceInitFunc
val'
        InstanceInitFunc -> IO InstanceInitFunc
forall (m :: * -> *) a. Monad m => a -> m a
return InstanceInitFunc
val''
    Maybe InstanceInitFunc -> IO (Maybe InstanceInitFunc)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe InstanceInitFunc
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 :: forall (m :: * -> *).
MonadIO m =>
TypeInfo -> FunPtr C_InstanceInitFunc -> m ()
setTypeInfoInstanceInit TypeInfo
s FunPtr C_InstanceInitFunc
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TypeInfo -> (Ptr TypeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO ()) -> IO ())
-> (Ptr TypeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    Ptr (FunPtr C_InstanceInitFunc)
-> FunPtr C_InstanceInitFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr (FunPtr C_InstanceInitFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56) (FunPtr C_InstanceInitFunc
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 :: forall (m :: * -> *). MonadIO m => TypeInfo -> m ()
clearTypeInfoInstanceInit TypeInfo
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TypeInfo -> (Ptr TypeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO ()) -> IO ())
-> (Ptr TypeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    Ptr (FunPtr C_InstanceInitFunc)
-> FunPtr C_InstanceInitFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr (FunPtr C_InstanceInitFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56) (FunPtr C_InstanceInitFunc
forall a. FunPtr a
FP.nullFunPtr :: FunPtr GObject.Callbacks.C_InstanceInitFunc)

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

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 :: forall (m :: * -> *).
MonadIO m =>
TypeInfo -> m (Maybe TypeValueTable)
getTypeInfoValueTable TypeInfo
s = IO (Maybe TypeValueTable) -> m (Maybe TypeValueTable)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TypeValueTable) -> m (Maybe TypeValueTable))
-> IO (Maybe TypeValueTable) -> m (Maybe TypeValueTable)
forall a b. (a -> b) -> a -> b
$ TypeInfo
-> (Ptr TypeInfo -> IO (Maybe TypeValueTable))
-> IO (Maybe TypeValueTable)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO (Maybe TypeValueTable))
 -> IO (Maybe TypeValueTable))
-> (Ptr TypeInfo -> IO (Maybe TypeValueTable))
-> IO (Maybe TypeValueTable)
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    Ptr TypeValueTable
val <- Ptr (Ptr TypeValueTable) -> IO (Ptr TypeValueTable)
forall a. Storable a => Ptr a -> IO a
peek (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr (Ptr TypeValueTable)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64) :: IO (Ptr GObject.TypeValueTable.TypeValueTable)
    Maybe TypeValueTable
result <- Ptr TypeValueTable
-> (Ptr TypeValueTable -> IO TypeValueTable)
-> IO (Maybe TypeValueTable)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr TypeValueTable
val ((Ptr TypeValueTable -> IO TypeValueTable)
 -> IO (Maybe TypeValueTable))
-> (Ptr TypeValueTable -> IO TypeValueTable)
-> IO (Maybe TypeValueTable)
forall a b. (a -> b) -> a -> b
$ \Ptr TypeValueTable
val' -> do
        TypeValueTable
val'' <- ((ManagedPtr TypeValueTable -> TypeValueTable)
-> Ptr TypeValueTable -> IO TypeValueTable
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr TypeValueTable -> TypeValueTable
GObject.TypeValueTable.TypeValueTable) Ptr TypeValueTable
val'
        TypeValueTable -> IO TypeValueTable
forall (m :: * -> *) a. Monad m => a -> m a
return TypeValueTable
val''
    Maybe TypeValueTable -> IO (Maybe TypeValueTable)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TypeValueTable
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 :: forall (m :: * -> *).
MonadIO m =>
TypeInfo -> Ptr TypeValueTable -> m ()
setTypeInfoValueTable TypeInfo
s Ptr TypeValueTable
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TypeInfo -> (Ptr TypeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO ()) -> IO ())
-> (Ptr TypeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    Ptr (Ptr TypeValueTable) -> Ptr TypeValueTable -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr (Ptr TypeValueTable)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64) (Ptr TypeValueTable
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 :: forall (m :: * -> *). MonadIO m => TypeInfo -> m ()
clearTypeInfoValueTable TypeInfo
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TypeInfo -> (Ptr TypeInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TypeInfo
s ((Ptr TypeInfo -> IO ()) -> IO ())
-> (Ptr TypeInfo -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TypeInfo
ptr -> do
    Ptr (Ptr TypeValueTable) -> Ptr TypeValueTable -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TypeInfo
ptr Ptr TypeInfo -> Int -> Ptr (Ptr TypeValueTable)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64) (Ptr TypeValueTable
forall a. Ptr a
FP.nullPtr :: Ptr GObject.TypeValueTable.TypeValueTable)

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

typeInfo_valueTable :: AttrLabelProxy "valueTable"
typeInfo_valueTable = AttrLabelProxy

#endif



#if defined(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 defined(ENABLE_OVERLOADING)
type family ResolveTypeInfoMethod (t :: Symbol) (o :: *) :: * where
    ResolveTypeInfoMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveTypeInfoMethod t TypeInfo, O.OverloadedMethod info TypeInfo p) => OL.IsLabel t (TypeInfo -> 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 ~ ResolveTypeInfoMethod t TypeInfo, O.OverloadedMethod info TypeInfo p, R.HasField t TypeInfo p) => R.HasField t TypeInfo p where
    getField = O.overloadedMethod @info

#endif

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

#endif