#define ENABLE_OVERLOADING (MIN_VERSION_haskell_gi_overloading(1,0,0) \
&& !defined(__HADDOCK_VERSION__))
module GI.GLib.Structs.MemVTable
(
MemVTable(..) ,
newZeroMemVTable ,
noMemVTable ,
clearMemVTableCalloc ,
getMemVTableCalloc ,
#if ENABLE_OVERLOADING
memVTable_calloc ,
#endif
setMemVTableCalloc ,
clearMemVTableFree ,
getMemVTableFree ,
#if ENABLE_OVERLOADING
memVTable_free ,
#endif
setMemVTableFree ,
clearMemVTableMalloc ,
getMemVTableMalloc ,
#if ENABLE_OVERLOADING
memVTable_malloc ,
#endif
setMemVTableMalloc ,
clearMemVTableRealloc ,
getMemVTableRealloc ,
#if ENABLE_OVERLOADING
memVTable_realloc ,
#endif
setMemVTableRealloc ,
clearMemVTableTryMalloc ,
getMemVTableTryMalloc ,
#if ENABLE_OVERLOADING
memVTable_tryMalloc ,
#endif
setMemVTableTryMalloc ,
clearMemVTableTryRealloc ,
getMemVTableTryRealloc ,
#if ENABLE_OVERLOADING
memVTable_tryRealloc ,
#endif
setMemVTableTryRealloc ,
) 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.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.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GI.GLib.Callbacks as GLib.Callbacks
newtype MemVTable = MemVTable (ManagedPtr MemVTable)
instance WrappedPtr MemVTable where
wrappedPtrCalloc = callocBytes 48
wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 48 >=> wrapPtr MemVTable)
wrappedPtrFree = Just ptr_to_g_free
newZeroMemVTable :: MonadIO m => m MemVTable
newZeroMemVTable = liftIO $ wrappedPtrCalloc >>= wrapPtr MemVTable
instance tag ~ 'AttrSet => Constructible MemVTable tag where
new _ attrs = do
o <- newZeroMemVTable
GI.Attributes.set o attrs
return o
noMemVTable :: Maybe MemVTable
noMemVTable = Nothing
getMemVTableMalloc :: MonadIO m => MemVTable -> m (Maybe GLib.Callbacks.MemVTableMallocFieldCallback)
getMemVTableMalloc s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 0) :: IO (FunPtr GLib.Callbacks.C_MemVTableMallocFieldCallback)
result <- SP.convertFunPtrIfNonNull val $ \val' -> do
let val'' = GLib.Callbacks.dynamic_MemVTableMallocFieldCallback val'
return val''
return result
setMemVTableMalloc :: MonadIO m => MemVTable -> FunPtr GLib.Callbacks.C_MemVTableMallocFieldCallback -> m ()
setMemVTableMalloc s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 0) (val :: FunPtr GLib.Callbacks.C_MemVTableMallocFieldCallback)
clearMemVTableMalloc :: MonadIO m => MemVTable -> m ()
clearMemVTableMalloc s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 0) (FP.nullFunPtr :: FunPtr GLib.Callbacks.C_MemVTableMallocFieldCallback)
#if ENABLE_OVERLOADING
data MemVTableMallocFieldInfo
instance AttrInfo MemVTableMallocFieldInfo where
type AttrAllowedOps MemVTableMallocFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint MemVTableMallocFieldInfo = (~) (FunPtr GLib.Callbacks.C_MemVTableMallocFieldCallback)
type AttrBaseTypeConstraint MemVTableMallocFieldInfo = (~) MemVTable
type AttrGetType MemVTableMallocFieldInfo = Maybe GLib.Callbacks.MemVTableMallocFieldCallback
type AttrLabel MemVTableMallocFieldInfo = "malloc"
type AttrOrigin MemVTableMallocFieldInfo = MemVTable
attrGet _ = getMemVTableMalloc
attrSet _ = setMemVTableMalloc
attrConstruct = undefined
attrClear _ = clearMemVTableMalloc
memVTable_malloc :: AttrLabelProxy "malloc"
memVTable_malloc = AttrLabelProxy
#endif
getMemVTableRealloc :: MonadIO m => MemVTable -> m (Maybe GLib.Callbacks.MemVTableReallocFieldCallback)
getMemVTableRealloc s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 8) :: IO (FunPtr GLib.Callbacks.C_MemVTableReallocFieldCallback)
result <- SP.convertFunPtrIfNonNull val $ \val' -> do
let val'' = GLib.Callbacks.dynamic_MemVTableReallocFieldCallback val'
return val''
return result
setMemVTableRealloc :: MonadIO m => MemVTable -> FunPtr GLib.Callbacks.C_MemVTableReallocFieldCallback -> m ()
setMemVTableRealloc s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (val :: FunPtr GLib.Callbacks.C_MemVTableReallocFieldCallback)
clearMemVTableRealloc :: MonadIO m => MemVTable -> m ()
clearMemVTableRealloc s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (FP.nullFunPtr :: FunPtr GLib.Callbacks.C_MemVTableReallocFieldCallback)
#if ENABLE_OVERLOADING
data MemVTableReallocFieldInfo
instance AttrInfo MemVTableReallocFieldInfo where
type AttrAllowedOps MemVTableReallocFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint MemVTableReallocFieldInfo = (~) (FunPtr GLib.Callbacks.C_MemVTableReallocFieldCallback)
type AttrBaseTypeConstraint MemVTableReallocFieldInfo = (~) MemVTable
type AttrGetType MemVTableReallocFieldInfo = Maybe GLib.Callbacks.MemVTableReallocFieldCallback
type AttrLabel MemVTableReallocFieldInfo = "realloc"
type AttrOrigin MemVTableReallocFieldInfo = MemVTable
attrGet _ = getMemVTableRealloc
attrSet _ = setMemVTableRealloc
attrConstruct = undefined
attrClear _ = clearMemVTableRealloc
memVTable_realloc :: AttrLabelProxy "realloc"
memVTable_realloc = AttrLabelProxy
#endif
getMemVTableFree :: MonadIO m => MemVTable -> m (Maybe GLib.Callbacks.MemVTableFreeFieldCallback)
getMemVTableFree s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 16) :: IO (FunPtr GLib.Callbacks.C_MemVTableFreeFieldCallback)
result <- SP.convertFunPtrIfNonNull val $ \val' -> do
let val'' = GLib.Callbacks.dynamic_MemVTableFreeFieldCallback val'
return val''
return result
setMemVTableFree :: MonadIO m => MemVTable -> FunPtr GLib.Callbacks.C_MemVTableFreeFieldCallback -> m ()
setMemVTableFree s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 16) (val :: FunPtr GLib.Callbacks.C_MemVTableFreeFieldCallback)
clearMemVTableFree :: MonadIO m => MemVTable -> m ()
clearMemVTableFree s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 16) (FP.nullFunPtr :: FunPtr GLib.Callbacks.C_MemVTableFreeFieldCallback)
#if ENABLE_OVERLOADING
data MemVTableFreeFieldInfo
instance AttrInfo MemVTableFreeFieldInfo where
type AttrAllowedOps MemVTableFreeFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint MemVTableFreeFieldInfo = (~) (FunPtr GLib.Callbacks.C_MemVTableFreeFieldCallback)
type AttrBaseTypeConstraint MemVTableFreeFieldInfo = (~) MemVTable
type AttrGetType MemVTableFreeFieldInfo = Maybe GLib.Callbacks.MemVTableFreeFieldCallback
type AttrLabel MemVTableFreeFieldInfo = "free"
type AttrOrigin MemVTableFreeFieldInfo = MemVTable
attrGet _ = getMemVTableFree
attrSet _ = setMemVTableFree
attrConstruct = undefined
attrClear _ = clearMemVTableFree
memVTable_free :: AttrLabelProxy "free"
memVTable_free = AttrLabelProxy
#endif
getMemVTableCalloc :: MonadIO m => MemVTable -> m (Maybe GLib.Callbacks.MemVTableCallocFieldCallback)
getMemVTableCalloc s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 24) :: IO (FunPtr GLib.Callbacks.C_MemVTableCallocFieldCallback)
result <- SP.convertFunPtrIfNonNull val $ \val' -> do
let val'' = GLib.Callbacks.dynamic_MemVTableCallocFieldCallback val'
return val''
return result
setMemVTableCalloc :: MonadIO m => MemVTable -> FunPtr GLib.Callbacks.C_MemVTableCallocFieldCallback -> m ()
setMemVTableCalloc s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 24) (val :: FunPtr GLib.Callbacks.C_MemVTableCallocFieldCallback)
clearMemVTableCalloc :: MonadIO m => MemVTable -> m ()
clearMemVTableCalloc s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 24) (FP.nullFunPtr :: FunPtr GLib.Callbacks.C_MemVTableCallocFieldCallback)
#if ENABLE_OVERLOADING
data MemVTableCallocFieldInfo
instance AttrInfo MemVTableCallocFieldInfo where
type AttrAllowedOps MemVTableCallocFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint MemVTableCallocFieldInfo = (~) (FunPtr GLib.Callbacks.C_MemVTableCallocFieldCallback)
type AttrBaseTypeConstraint MemVTableCallocFieldInfo = (~) MemVTable
type AttrGetType MemVTableCallocFieldInfo = Maybe GLib.Callbacks.MemVTableCallocFieldCallback
type AttrLabel MemVTableCallocFieldInfo = "calloc"
type AttrOrigin MemVTableCallocFieldInfo = MemVTable
attrGet _ = getMemVTableCalloc
attrSet _ = setMemVTableCalloc
attrConstruct = undefined
attrClear _ = clearMemVTableCalloc
memVTable_calloc :: AttrLabelProxy "calloc"
memVTable_calloc = AttrLabelProxy
#endif
getMemVTableTryMalloc :: MonadIO m => MemVTable -> m (Maybe GLib.Callbacks.MemVTableTryMallocFieldCallback)
getMemVTableTryMalloc s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 32) :: IO (FunPtr GLib.Callbacks.C_MemVTableTryMallocFieldCallback)
result <- SP.convertFunPtrIfNonNull val $ \val' -> do
let val'' = GLib.Callbacks.dynamic_MemVTableTryMallocFieldCallback val'
return val''
return result
setMemVTableTryMalloc :: MonadIO m => MemVTable -> FunPtr GLib.Callbacks.C_MemVTableTryMallocFieldCallback -> m ()
setMemVTableTryMalloc s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 32) (val :: FunPtr GLib.Callbacks.C_MemVTableTryMallocFieldCallback)
clearMemVTableTryMalloc :: MonadIO m => MemVTable -> m ()
clearMemVTableTryMalloc s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 32) (FP.nullFunPtr :: FunPtr GLib.Callbacks.C_MemVTableTryMallocFieldCallback)
#if ENABLE_OVERLOADING
data MemVTableTryMallocFieldInfo
instance AttrInfo MemVTableTryMallocFieldInfo where
type AttrAllowedOps MemVTableTryMallocFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint MemVTableTryMallocFieldInfo = (~) (FunPtr GLib.Callbacks.C_MemVTableTryMallocFieldCallback)
type AttrBaseTypeConstraint MemVTableTryMallocFieldInfo = (~) MemVTable
type AttrGetType MemVTableTryMallocFieldInfo = Maybe GLib.Callbacks.MemVTableTryMallocFieldCallback
type AttrLabel MemVTableTryMallocFieldInfo = "try_malloc"
type AttrOrigin MemVTableTryMallocFieldInfo = MemVTable
attrGet _ = getMemVTableTryMalloc
attrSet _ = setMemVTableTryMalloc
attrConstruct = undefined
attrClear _ = clearMemVTableTryMalloc
memVTable_tryMalloc :: AttrLabelProxy "tryMalloc"
memVTable_tryMalloc = AttrLabelProxy
#endif
getMemVTableTryRealloc :: MonadIO m => MemVTable -> m (Maybe GLib.Callbacks.MemVTableTryReallocFieldCallback)
getMemVTableTryRealloc s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 40) :: IO (FunPtr GLib.Callbacks.C_MemVTableTryReallocFieldCallback)
result <- SP.convertFunPtrIfNonNull val $ \val' -> do
let val'' = GLib.Callbacks.dynamic_MemVTableTryReallocFieldCallback val'
return val''
return result
setMemVTableTryRealloc :: MonadIO m => MemVTable -> FunPtr GLib.Callbacks.C_MemVTableTryReallocFieldCallback -> m ()
setMemVTableTryRealloc s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 40) (val :: FunPtr GLib.Callbacks.C_MemVTableTryReallocFieldCallback)
clearMemVTableTryRealloc :: MonadIO m => MemVTable -> m ()
clearMemVTableTryRealloc s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 40) (FP.nullFunPtr :: FunPtr GLib.Callbacks.C_MemVTableTryReallocFieldCallback)
#if ENABLE_OVERLOADING
data MemVTableTryReallocFieldInfo
instance AttrInfo MemVTableTryReallocFieldInfo where
type AttrAllowedOps MemVTableTryReallocFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint MemVTableTryReallocFieldInfo = (~) (FunPtr GLib.Callbacks.C_MemVTableTryReallocFieldCallback)
type AttrBaseTypeConstraint MemVTableTryReallocFieldInfo = (~) MemVTable
type AttrGetType MemVTableTryReallocFieldInfo = Maybe GLib.Callbacks.MemVTableTryReallocFieldCallback
type AttrLabel MemVTableTryReallocFieldInfo = "try_realloc"
type AttrOrigin MemVTableTryReallocFieldInfo = MemVTable
attrGet _ = getMemVTableTryRealloc
attrSet _ = setMemVTableTryRealloc
attrConstruct = undefined
attrClear _ = clearMemVTableTryRealloc
memVTable_tryRealloc :: AttrLabelProxy "tryRealloc"
memVTable_tryRealloc = AttrLabelProxy
#endif
#if ENABLE_OVERLOADING
instance O.HasAttributeList MemVTable
type instance O.AttributeList MemVTable = MemVTableAttributeList
type MemVTableAttributeList = ('[ '("malloc", MemVTableMallocFieldInfo), '("realloc", MemVTableReallocFieldInfo), '("free", MemVTableFreeFieldInfo), '("calloc", MemVTableCallocFieldInfo), '("tryMalloc", MemVTableTryMallocFieldInfo), '("tryRealloc", MemVTableTryReallocFieldInfo)] :: [(Symbol, *)])
#endif
#if ENABLE_OVERLOADING
type family ResolveMemVTableMethod (t :: Symbol) (o :: *) :: * where
ResolveMemVTableMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveMemVTableMethod t MemVTable, O.MethodInfo info MemVTable p) => O.IsLabelProxy t (MemVTable -> p) where
fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveMemVTableMethod t MemVTable, O.MethodInfo info MemVTable p) => O.IsLabel t (MemVTable -> 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
#endif