{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- An opaque data structure representing String Chunks.
-- It should only be accessed by using the following functions.

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

module GI.GLib.Structs.StringChunk
    ( 

-- * Exported types
    StringChunk(..)                         ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [clear]("GI.GLib.Structs.StringChunk#g:method:clear"), [free]("GI.GLib.Structs.StringChunk#g:method:free"), [insert]("GI.GLib.Structs.StringChunk#g:method:insert"), [insertConst]("GI.GLib.Structs.StringChunk#g:method:insertConst"), [insertLen]("GI.GLib.Structs.StringChunk#g:method:insertLen").
-- 
-- ==== Getters
-- /None/.
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveStringChunkMethod                ,
#endif

-- ** clear #method:clear#

#if defined(ENABLE_OVERLOADING)
    StringChunkClearMethodInfo              ,
#endif
    stringChunkClear                        ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    StringChunkFreeMethodInfo               ,
#endif
    stringChunkFree                         ,


-- ** insert #method:insert#

#if defined(ENABLE_OVERLOADING)
    StringChunkInsertMethodInfo             ,
#endif
    stringChunkInsert                       ,


-- ** insertConst #method:insertConst#

#if defined(ENABLE_OVERLOADING)
    StringChunkInsertConstMethodInfo        ,
#endif
    stringChunkInsertConst                  ,


-- ** insertLen #method:insertLen#

#if defined(ENABLE_OVERLOADING)
    StringChunkInsertLenMethodInfo          ,
#endif
    stringChunkInsertLen                    ,




    ) 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


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

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

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


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList StringChunk
type instance O.AttributeList StringChunk = StringChunkAttributeList
type StringChunkAttributeList = ('[ ] :: [(Symbol, *)])
#endif

-- method StringChunk::clear
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "chunk"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "StringChunk" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GStringChunk" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_string_chunk_clear" g_string_chunk_clear :: 
    Ptr StringChunk ->                      -- chunk : TInterface (Name {namespace = "GLib", name = "StringChunk"})
    IO ()

-- | Frees all strings contained within the t'GI.GLib.Structs.StringChunk.StringChunk'.
-- After calling 'GI.GLib.Structs.StringChunk.stringChunkClear' it is not safe to
-- access any of the strings which were contained within it.
-- 
-- /Since: 2.14/
stringChunkClear ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    StringChunk
    -- ^ /@chunk@/: a t'GI.GLib.Structs.StringChunk.StringChunk'
    -> m ()
stringChunkClear :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
StringChunk -> m ()
stringChunkClear StringChunk
chunk = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr StringChunk
chunk' <- StringChunk -> IO (Ptr StringChunk)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr StringChunk
chunk
    Ptr StringChunk -> IO ()
g_string_chunk_clear Ptr StringChunk
chunk'
    StringChunk -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr StringChunk
chunk
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data StringChunkClearMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod StringChunkClearMethodInfo StringChunk signature where
    overloadedMethod = stringChunkClear

instance O.OverloadedMethodInfo StringChunkClearMethodInfo StringChunk where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GLib.Structs.StringChunk.stringChunkClear",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-glib-2.0.25/docs/GI-GLib-Structs-StringChunk.html#v:stringChunkClear"
        }


#endif

-- method StringChunk::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "chunk"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "StringChunk" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GStringChunk" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_string_chunk_free" g_string_chunk_free :: 
    Ptr StringChunk ->                      -- chunk : TInterface (Name {namespace = "GLib", name = "StringChunk"})
    IO ()

-- | Frees all memory allocated by the t'GI.GLib.Structs.StringChunk.StringChunk'.
-- After calling 'GI.GLib.Structs.StringChunk.stringChunkFree' it is not safe to
-- access any of the strings which were contained within it.
stringChunkFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    StringChunk
    -- ^ /@chunk@/: a t'GI.GLib.Structs.StringChunk.StringChunk'
    -> m ()
stringChunkFree :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
StringChunk -> m ()
stringChunkFree StringChunk
chunk = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr StringChunk
chunk' <- StringChunk -> IO (Ptr StringChunk)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr StringChunk
chunk
    Ptr StringChunk -> IO ()
g_string_chunk_free Ptr StringChunk
chunk'
    StringChunk -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr StringChunk
chunk
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data StringChunkFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod StringChunkFreeMethodInfo StringChunk signature where
    overloadedMethod = stringChunkFree

instance O.OverloadedMethodInfo StringChunkFreeMethodInfo StringChunk where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GLib.Structs.StringChunk.stringChunkFree",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-glib-2.0.25/docs/GI-GLib-Structs-StringChunk.html#v:stringChunkFree"
        }


#endif

-- method StringChunk::insert
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "chunk"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "StringChunk" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GStringChunk" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "string"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the string to add" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_string_chunk_insert" g_string_chunk_insert :: 
    Ptr StringChunk ->                      -- chunk : TInterface (Name {namespace = "GLib", name = "StringChunk"})
    CString ->                              -- string : TBasicType TUTF8
    IO CString

-- | Adds a copy of /@string@/ to the t'GI.GLib.Structs.StringChunk.StringChunk'.
-- It returns a pointer to the new copy of the string
-- in the t'GI.GLib.Structs.StringChunk.StringChunk'. The characters in the string
-- can be changed, if necessary, though you should not
-- change anything after the end of the string.
-- 
-- Unlike 'GI.GLib.Structs.StringChunk.stringChunkInsertConst', this function
-- does not check for duplicates. Also strings added
-- with 'GI.GLib.Structs.StringChunk.stringChunkInsert' will not be searched
-- by 'GI.GLib.Structs.StringChunk.stringChunkInsertConst' when looking for
-- duplicates.
stringChunkInsert ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    StringChunk
    -- ^ /@chunk@/: a t'GI.GLib.Structs.StringChunk.StringChunk'
    -> T.Text
    -- ^ /@string@/: the string to add
    -> m T.Text
    -- ^ __Returns:__ a pointer to the copy of /@string@/ within
    --     the t'GI.GLib.Structs.StringChunk.StringChunk'
stringChunkInsert :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
StringChunk -> Text -> m Text
stringChunkInsert StringChunk
chunk Text
string = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr StringChunk
chunk' <- StringChunk -> IO (Ptr StringChunk)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr StringChunk
chunk
    CString
string' <- Text -> IO CString
textToCString Text
string
    CString
result <- Ptr StringChunk -> CString -> IO CString
g_string_chunk_insert Ptr StringChunk
chunk' CString
string'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringChunkInsert" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    StringChunk -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr StringChunk
chunk
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
string'
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data StringChunkInsertMethodInfo
instance (signature ~ (T.Text -> m T.Text), MonadIO m) => O.OverloadedMethod StringChunkInsertMethodInfo StringChunk signature where
    overloadedMethod = stringChunkInsert

instance O.OverloadedMethodInfo StringChunkInsertMethodInfo StringChunk where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GLib.Structs.StringChunk.stringChunkInsert",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-glib-2.0.25/docs/GI-GLib-Structs-StringChunk.html#v:stringChunkInsert"
        }


#endif

-- method StringChunk::insert_const
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "chunk"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "StringChunk" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GStringChunk" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "string"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the string to add" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_string_chunk_insert_const" g_string_chunk_insert_const :: 
    Ptr StringChunk ->                      -- chunk : TInterface (Name {namespace = "GLib", name = "StringChunk"})
    CString ->                              -- string : TBasicType TUTF8
    IO CString

-- | Adds a copy of /@string@/ to the t'GI.GLib.Structs.StringChunk.StringChunk', unless the same
-- string has already been added to the t'GI.GLib.Structs.StringChunk.StringChunk' with
-- 'GI.GLib.Structs.StringChunk.stringChunkInsertConst'.
-- 
-- This function is useful if you need to copy a large number
-- of strings but do not want to waste space storing duplicates.
-- But you must remember that there may be several pointers to
-- the same string, and so any changes made to the strings
-- should be done very carefully.
-- 
-- Note that 'GI.GLib.Structs.StringChunk.stringChunkInsertConst' will not return a
-- pointer to a string added with 'GI.GLib.Structs.StringChunk.stringChunkInsert', even
-- if they do match.
stringChunkInsertConst ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    StringChunk
    -- ^ /@chunk@/: a t'GI.GLib.Structs.StringChunk.StringChunk'
    -> T.Text
    -- ^ /@string@/: the string to add
    -> m T.Text
    -- ^ __Returns:__ a pointer to the new or existing copy of /@string@/
    --     within the t'GI.GLib.Structs.StringChunk.StringChunk'
stringChunkInsertConst :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
StringChunk -> Text -> m Text
stringChunkInsertConst StringChunk
chunk Text
string = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr StringChunk
chunk' <- StringChunk -> IO (Ptr StringChunk)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr StringChunk
chunk
    CString
string' <- Text -> IO CString
textToCString Text
string
    CString
result <- Ptr StringChunk -> CString -> IO CString
g_string_chunk_insert_const Ptr StringChunk
chunk' CString
string'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringChunkInsertConst" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    StringChunk -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr StringChunk
chunk
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
string'
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data StringChunkInsertConstMethodInfo
instance (signature ~ (T.Text -> m T.Text), MonadIO m) => O.OverloadedMethod StringChunkInsertConstMethodInfo StringChunk signature where
    overloadedMethod = stringChunkInsertConst

instance O.OverloadedMethodInfo StringChunkInsertConstMethodInfo StringChunk where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GLib.Structs.StringChunk.stringChunkInsertConst",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-glib-2.0.25/docs/GI-GLib-Structs-StringChunk.html#v:stringChunkInsertConst"
        }


#endif

-- method StringChunk::insert_len
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "chunk"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "StringChunk" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GStringChunk" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "string"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "bytes to insert" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "len"
--           , argType = TBasicType TInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "number of bytes of @string to insert, or -1 to insert a\n    nul-terminated string"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_string_chunk_insert_len" g_string_chunk_insert_len :: 
    Ptr StringChunk ->                      -- chunk : TInterface (Name {namespace = "GLib", name = "StringChunk"})
    CString ->                              -- string : TBasicType TUTF8
    Int64 ->                                -- len : TBasicType TInt64
    IO CString

-- | Adds a copy of the first /@len@/ bytes of /@string@/ to the t'GI.GLib.Structs.StringChunk.StringChunk'.
-- The copy is nul-terminated.
-- 
-- Since this function does not stop at nul bytes, it is the caller\'s
-- responsibility to ensure that /@string@/ has at least /@len@/ addressable
-- bytes.
-- 
-- The characters in the returned string can be changed, if necessary,
-- though you should not change anything after the end of the string.
-- 
-- /Since: 2.4/
stringChunkInsertLen ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    StringChunk
    -- ^ /@chunk@/: a t'GI.GLib.Structs.StringChunk.StringChunk'
    -> T.Text
    -- ^ /@string@/: bytes to insert
    -> Int64
    -- ^ /@len@/: number of bytes of /@string@/ to insert, or -1 to insert a
    --     nul-terminated string
    -> m T.Text
    -- ^ __Returns:__ a pointer to the copy of /@string@/ within the t'GI.GLib.Structs.StringChunk.StringChunk'
stringChunkInsertLen :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
StringChunk -> Text -> Int64 -> m Text
stringChunkInsertLen StringChunk
chunk Text
string Int64
len = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr StringChunk
chunk' <- StringChunk -> IO (Ptr StringChunk)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr StringChunk
chunk
    CString
string' <- Text -> IO CString
textToCString Text
string
    CString
result <- Ptr StringChunk -> CString -> Int64 -> IO CString
g_string_chunk_insert_len Ptr StringChunk
chunk' CString
string' Int64
len
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringChunkInsertLen" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    StringChunk -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr StringChunk
chunk
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
string'
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data StringChunkInsertLenMethodInfo
instance (signature ~ (T.Text -> Int64 -> m T.Text), MonadIO m) => O.OverloadedMethod StringChunkInsertLenMethodInfo StringChunk signature where
    overloadedMethod = stringChunkInsertLen

instance O.OverloadedMethodInfo StringChunkInsertLenMethodInfo StringChunk where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GLib.Structs.StringChunk.stringChunkInsertLen",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-glib-2.0.25/docs/GI-GLib-Structs-StringChunk.html#v:stringChunkInsertLen"
        }


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveStringChunkMethod (t :: Symbol) (o :: *) :: * where
    ResolveStringChunkMethod "clear" o = StringChunkClearMethodInfo
    ResolveStringChunkMethod "free" o = StringChunkFreeMethodInfo
    ResolveStringChunkMethod "insert" o = StringChunkInsertMethodInfo
    ResolveStringChunkMethod "insertConst" o = StringChunkInsertConstMethodInfo
    ResolveStringChunkMethod "insertLen" o = StringChunkInsertLenMethodInfo
    ResolveStringChunkMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif