{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.GLib.Structs.MemChunk
    ( 

-- * Exported types
    MemChunk(..)                            ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [alloc]("GI.GLib.Structs.MemChunk#g:method:alloc"), [alloc0]("GI.GLib.Structs.MemChunk#g:method:alloc0"), [clean]("GI.GLib.Structs.MemChunk#g:method:clean"), [destroy]("GI.GLib.Structs.MemChunk#g:method:destroy"), [free]("GI.GLib.Structs.MemChunk#g:method:free"), [print]("GI.GLib.Structs.MemChunk#g:method:print"), [reset]("GI.GLib.Structs.MemChunk#g:method:reset").
-- 
-- ==== Getters
-- /None/.
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveMemChunkMethod                   ,
#endif

-- ** alloc #method:alloc#

#if defined(ENABLE_OVERLOADING)
    MemChunkAllocMethodInfo                 ,
#endif
    memChunkAlloc                           ,


-- ** alloc0 #method:alloc0#

#if defined(ENABLE_OVERLOADING)
    MemChunkAlloc0MethodInfo                ,
#endif
    memChunkAlloc0                          ,


-- ** clean #method:clean#

#if defined(ENABLE_OVERLOADING)
    MemChunkCleanMethodInfo                 ,
#endif
    memChunkClean                           ,


-- ** destroy #method:destroy#

#if defined(ENABLE_OVERLOADING)
    MemChunkDestroyMethodInfo               ,
#endif
    memChunkDestroy                         ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    MemChunkFreeMethodInfo                  ,
#endif
    memChunkFree                            ,


-- ** info #method:info#

    memChunkInfo                            ,


-- ** print #method:print#

#if defined(ENABLE_OVERLOADING)
    MemChunkPrintMethodInfo                 ,
#endif
    memChunkPrint                           ,


-- ** reset #method:reset#

#if defined(ENABLE_OVERLOADING)
    MemChunkResetMethodInfo                 ,
#endif
    memChunkReset                           ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)

#else

#endif

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

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

-- XXX Wrapping a foreign struct/union with no known destructor or size, leak?
instance BoxedPtr MemChunk where
    boxedPtrCopy :: MemChunk -> IO MemChunk
boxedPtrCopy = MemChunk -> IO MemChunk
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return
    boxedPtrFree :: MemChunk -> IO ()
boxedPtrFree = \MemChunk
_x -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList MemChunk
type instance O.AttributeList MemChunk = MemChunkAttributeList
type MemChunkAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif

-- method MemChunk::alloc
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mem_chunk"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "MemChunk" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TPtr)
-- throws : False
-- Skip return : False

foreign import ccall "g_mem_chunk_alloc" g_mem_chunk_alloc :: 
    Ptr MemChunk ->                         -- mem_chunk : TInterface (Name {namespace = "GLib", name = "MemChunk"})
    IO (Ptr ())

-- | /No description available in the introspection data./
memChunkAlloc ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MemChunk
    -> m (Ptr ())
memChunkAlloc :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
MemChunk -> m (Ptr ())
memChunkAlloc MemChunk
memChunk = IO (Ptr ()) -> m (Ptr ())
forall a. IO a -> m a
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
$ do
    Ptr MemChunk
memChunk' <- MemChunk -> IO (Ptr MemChunk)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MemChunk
memChunk
    Ptr ()
result <- Ptr MemChunk -> IO (Ptr ())
g_mem_chunk_alloc Ptr MemChunk
memChunk'
    MemChunk -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MemChunk
memChunk
    Ptr () -> IO (Ptr ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data MemChunkAllocMethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m) => O.OverloadedMethod MemChunkAllocMethodInfo MemChunk signature where
    overloadedMethod = memChunkAlloc

instance O.OverloadedMethodInfo MemChunkAllocMethodInfo MemChunk where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.MemChunk.memChunkAlloc",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-MemChunk.html#v:memChunkAlloc"
        })


#endif

-- method MemChunk::alloc0
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mem_chunk"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "MemChunk" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TPtr)
-- throws : False
-- Skip return : False

foreign import ccall "g_mem_chunk_alloc0" g_mem_chunk_alloc0 :: 
    Ptr MemChunk ->                         -- mem_chunk : TInterface (Name {namespace = "GLib", name = "MemChunk"})
    IO (Ptr ())

-- | /No description available in the introspection data./
memChunkAlloc0 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MemChunk
    -> m (Ptr ())
memChunkAlloc0 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
MemChunk -> m (Ptr ())
memChunkAlloc0 MemChunk
memChunk = IO (Ptr ()) -> m (Ptr ())
forall a. IO a -> m a
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
$ do
    Ptr MemChunk
memChunk' <- MemChunk -> IO (Ptr MemChunk)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MemChunk
memChunk
    Ptr ()
result <- Ptr MemChunk -> IO (Ptr ())
g_mem_chunk_alloc0 Ptr MemChunk
memChunk'
    MemChunk -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MemChunk
memChunk
    Ptr () -> IO (Ptr ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result

#if defined(ENABLE_OVERLOADING)
data MemChunkAlloc0MethodInfo
instance (signature ~ (m (Ptr ())), MonadIO m) => O.OverloadedMethod MemChunkAlloc0MethodInfo MemChunk signature where
    overloadedMethod = memChunkAlloc0

instance O.OverloadedMethodInfo MemChunkAlloc0MethodInfo MemChunk where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.MemChunk.memChunkAlloc0",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-MemChunk.html#v:memChunkAlloc0"
        })


#endif

-- method MemChunk::clean
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mem_chunk"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "MemChunk" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_mem_chunk_clean" g_mem_chunk_clean :: 
    Ptr MemChunk ->                         -- mem_chunk : TInterface (Name {namespace = "GLib", name = "MemChunk"})
    IO ()

-- | /No description available in the introspection data./
memChunkClean ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MemChunk
    -> m ()
memChunkClean :: forall (m :: * -> *). (HasCallStack, MonadIO m) => MemChunk -> m ()
memChunkClean MemChunk
memChunk = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr MemChunk
memChunk' <- MemChunk -> IO (Ptr MemChunk)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MemChunk
memChunk
    Ptr MemChunk -> IO ()
g_mem_chunk_clean Ptr MemChunk
memChunk'
    MemChunk -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MemChunk
memChunk
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MemChunkCleanMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod MemChunkCleanMethodInfo MemChunk signature where
    overloadedMethod = memChunkClean

instance O.OverloadedMethodInfo MemChunkCleanMethodInfo MemChunk where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.MemChunk.memChunkClean",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-MemChunk.html#v:memChunkClean"
        })


#endif

-- method MemChunk::destroy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mem_chunk"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "MemChunk" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_mem_chunk_destroy" g_mem_chunk_destroy :: 
    Ptr MemChunk ->                         -- mem_chunk : TInterface (Name {namespace = "GLib", name = "MemChunk"})
    IO ()

-- | /No description available in the introspection data./
memChunkDestroy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MemChunk
    -> m ()
memChunkDestroy :: forall (m :: * -> *). (HasCallStack, MonadIO m) => MemChunk -> m ()
memChunkDestroy MemChunk
memChunk = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr MemChunk
memChunk' <- MemChunk -> IO (Ptr MemChunk)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MemChunk
memChunk
    Ptr MemChunk -> IO ()
g_mem_chunk_destroy Ptr MemChunk
memChunk'
    MemChunk -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MemChunk
memChunk
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MemChunkDestroyMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod MemChunkDestroyMethodInfo MemChunk signature where
    overloadedMethod = memChunkDestroy

instance O.OverloadedMethodInfo MemChunkDestroyMethodInfo MemChunk where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.MemChunk.memChunkDestroy",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-MemChunk.html#v:memChunkDestroy"
        })


#endif

-- method MemChunk::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mem_chunk"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "MemChunk" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "mem"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_mem_chunk_free" g_mem_chunk_free :: 
    Ptr MemChunk ->                         -- mem_chunk : TInterface (Name {namespace = "GLib", name = "MemChunk"})
    Ptr () ->                               -- mem : TBasicType TPtr
    IO ()

-- | /No description available in the introspection data./
memChunkFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MemChunk
    -> Ptr ()
    -> m ()
memChunkFree :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
MemChunk -> Ptr () -> m ()
memChunkFree MemChunk
memChunk Ptr ()
mem = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr MemChunk
memChunk' <- MemChunk -> IO (Ptr MemChunk)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MemChunk
memChunk
    Ptr MemChunk -> Ptr () -> IO ()
g_mem_chunk_free Ptr MemChunk
memChunk' Ptr ()
mem
    MemChunk -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MemChunk
memChunk
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MemChunkFreeMethodInfo
instance (signature ~ (Ptr () -> m ()), MonadIO m) => O.OverloadedMethod MemChunkFreeMethodInfo MemChunk signature where
    overloadedMethod = memChunkFree

instance O.OverloadedMethodInfo MemChunkFreeMethodInfo MemChunk where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.MemChunk.memChunkFree",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-MemChunk.html#v:memChunkFree"
        })


#endif

-- method MemChunk::print
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mem_chunk"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "MemChunk" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_mem_chunk_print" g_mem_chunk_print :: 
    Ptr MemChunk ->                         -- mem_chunk : TInterface (Name {namespace = "GLib", name = "MemChunk"})
    IO ()

-- | /No description available in the introspection data./
memChunkPrint ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MemChunk
    -> m ()
memChunkPrint :: forall (m :: * -> *). (HasCallStack, MonadIO m) => MemChunk -> m ()
memChunkPrint MemChunk
memChunk = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr MemChunk
memChunk' <- MemChunk -> IO (Ptr MemChunk)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MemChunk
memChunk
    Ptr MemChunk -> IO ()
g_mem_chunk_print Ptr MemChunk
memChunk'
    MemChunk -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MemChunk
memChunk
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MemChunkPrintMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod MemChunkPrintMethodInfo MemChunk signature where
    overloadedMethod = memChunkPrint

instance O.OverloadedMethodInfo MemChunkPrintMethodInfo MemChunk where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.MemChunk.memChunkPrint",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-MemChunk.html#v:memChunkPrint"
        })


#endif

-- method MemChunk::reset
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "mem_chunk"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "MemChunk" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_mem_chunk_reset" g_mem_chunk_reset :: 
    Ptr MemChunk ->                         -- mem_chunk : TInterface (Name {namespace = "GLib", name = "MemChunk"})
    IO ()

-- | /No description available in the introspection data./
memChunkReset ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MemChunk
    -> m ()
memChunkReset :: forall (m :: * -> *). (HasCallStack, MonadIO m) => MemChunk -> m ()
memChunkReset MemChunk
memChunk = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr MemChunk
memChunk' <- MemChunk -> IO (Ptr MemChunk)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MemChunk
memChunk
    Ptr MemChunk -> IO ()
g_mem_chunk_reset Ptr MemChunk
memChunk'
    MemChunk -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MemChunk
memChunk
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MemChunkResetMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod MemChunkResetMethodInfo MemChunk signature where
    overloadedMethod = memChunkReset

instance O.OverloadedMethodInfo MemChunkResetMethodInfo MemChunk where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.MemChunk.memChunkReset",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-MemChunk.html#v:memChunkReset"
        })


#endif

-- method MemChunk::info
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_mem_chunk_info" g_mem_chunk_info :: 
    IO ()

-- | /No description available in the introspection data./
memChunkInfo ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m ()
memChunkInfo :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m ()
memChunkInfo  = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    IO ()
g_mem_chunk_info
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveMemChunkMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveMemChunkMethod "alloc" o = MemChunkAllocMethodInfo
    ResolveMemChunkMethod "alloc0" o = MemChunkAlloc0MethodInfo
    ResolveMemChunkMethod "clean" o = MemChunkCleanMethodInfo
    ResolveMemChunkMethod "destroy" o = MemChunkDestroyMethodInfo
    ResolveMemChunkMethod "free" o = MemChunkFreeMethodInfo
    ResolveMemChunkMethod "print" o = MemChunkPrintMethodInfo
    ResolveMemChunkMethod "reset" o = MemChunkResetMethodInfo
    ResolveMemChunkMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif