{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The GString struct contains the public fields of a GString.

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

module GI.GLib.Structs.String
    ( 

-- * Exported types
    String(..)                              ,
    newZeroString                           ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [append]("GI.GLib.Structs.String#g:method:append"), [appendC]("GI.GLib.Structs.String#g:method:appendC"), [appendLen]("GI.GLib.Structs.String#g:method:appendLen"), [appendUnichar]("GI.GLib.Structs.String#g:method:appendUnichar"), [appendUriEscaped]("GI.GLib.Structs.String#g:method:appendUriEscaped"), [asciiDown]("GI.GLib.Structs.String#g:method:asciiDown"), [asciiUp]("GI.GLib.Structs.String#g:method:asciiUp"), [assign]("GI.GLib.Structs.String#g:method:assign"), [down]("GI.GLib.Structs.String#g:method:down"), [equal]("GI.GLib.Structs.String#g:method:equal"), [erase]("GI.GLib.Structs.String#g:method:erase"), [free]("GI.GLib.Structs.String#g:method:free"), [freeToBytes]("GI.GLib.Structs.String#g:method:freeToBytes"), [hash]("GI.GLib.Structs.String#g:method:hash"), [insert]("GI.GLib.Structs.String#g:method:insert"), [insertC]("GI.GLib.Structs.String#g:method:insertC"), [insertLen]("GI.GLib.Structs.String#g:method:insertLen"), [insertUnichar]("GI.GLib.Structs.String#g:method:insertUnichar"), [overwrite]("GI.GLib.Structs.String#g:method:overwrite"), [overwriteLen]("GI.GLib.Structs.String#g:method:overwriteLen"), [prepend]("GI.GLib.Structs.String#g:method:prepend"), [prependC]("GI.GLib.Structs.String#g:method:prependC"), [prependLen]("GI.GLib.Structs.String#g:method:prependLen"), [prependUnichar]("GI.GLib.Structs.String#g:method:prependUnichar"), [replace]("GI.GLib.Structs.String#g:method:replace"), [truncate]("GI.GLib.Structs.String#g:method:truncate"), [up]("GI.GLib.Structs.String#g:method:up").
-- 
-- ==== Getters
-- /None/.
-- 
-- ==== Setters
-- [setSize]("GI.GLib.Structs.String#g:method:setSize").

#if defined(ENABLE_OVERLOADING)
    ResolveStringMethod                     ,
#endif

-- ** append #method:append#

#if defined(ENABLE_OVERLOADING)
    StringAppendMethodInfo                  ,
#endif
    stringAppend                            ,


-- ** appendC #method:appendC#

#if defined(ENABLE_OVERLOADING)
    StringAppendCMethodInfo                 ,
#endif
    stringAppendC                           ,


-- ** appendLen #method:appendLen#

#if defined(ENABLE_OVERLOADING)
    StringAppendLenMethodInfo               ,
#endif
    stringAppendLen                         ,


-- ** appendUnichar #method:appendUnichar#

#if defined(ENABLE_OVERLOADING)
    StringAppendUnicharMethodInfo           ,
#endif
    stringAppendUnichar                     ,


-- ** appendUriEscaped #method:appendUriEscaped#

#if defined(ENABLE_OVERLOADING)
    StringAppendUriEscapedMethodInfo        ,
#endif
    stringAppendUriEscaped                  ,


-- ** asciiDown #method:asciiDown#

#if defined(ENABLE_OVERLOADING)
    StringAsciiDownMethodInfo               ,
#endif
    stringAsciiDown                         ,


-- ** asciiUp #method:asciiUp#

#if defined(ENABLE_OVERLOADING)
    StringAsciiUpMethodInfo                 ,
#endif
    stringAsciiUp                           ,


-- ** assign #method:assign#

#if defined(ENABLE_OVERLOADING)
    StringAssignMethodInfo                  ,
#endif
    stringAssign                            ,


-- ** down #method:down#

#if defined(ENABLE_OVERLOADING)
    StringDownMethodInfo                    ,
#endif
    stringDown                              ,


-- ** equal #method:equal#

#if defined(ENABLE_OVERLOADING)
    StringEqualMethodInfo                   ,
#endif
    stringEqual                             ,


-- ** erase #method:erase#

#if defined(ENABLE_OVERLOADING)
    StringEraseMethodInfo                   ,
#endif
    stringErase                             ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    StringFreeMethodInfo                    ,
#endif
    stringFree                              ,


-- ** freeToBytes #method:freeToBytes#

#if defined(ENABLE_OVERLOADING)
    StringFreeToBytesMethodInfo             ,
#endif
    stringFreeToBytes                       ,


-- ** hash #method:hash#

#if defined(ENABLE_OVERLOADING)
    StringHashMethodInfo                    ,
#endif
    stringHash                              ,


-- ** insert #method:insert#

#if defined(ENABLE_OVERLOADING)
    StringInsertMethodInfo                  ,
#endif
    stringInsert                            ,


-- ** insertC #method:insertC#

#if defined(ENABLE_OVERLOADING)
    StringInsertCMethodInfo                 ,
#endif
    stringInsertC                           ,


-- ** insertLen #method:insertLen#

#if defined(ENABLE_OVERLOADING)
    StringInsertLenMethodInfo               ,
#endif
    stringInsertLen                         ,


-- ** insertUnichar #method:insertUnichar#

#if defined(ENABLE_OVERLOADING)
    StringInsertUnicharMethodInfo           ,
#endif
    stringInsertUnichar                     ,


-- ** new #method:new#

    stringNew                               ,


-- ** newLen #method:newLen#

    stringNewLen                            ,


-- ** overwrite #method:overwrite#

#if defined(ENABLE_OVERLOADING)
    StringOverwriteMethodInfo               ,
#endif
    stringOverwrite                         ,


-- ** overwriteLen #method:overwriteLen#

#if defined(ENABLE_OVERLOADING)
    StringOverwriteLenMethodInfo            ,
#endif
    stringOverwriteLen                      ,


-- ** prepend #method:prepend#

#if defined(ENABLE_OVERLOADING)
    StringPrependMethodInfo                 ,
#endif
    stringPrepend                           ,


-- ** prependC #method:prependC#

#if defined(ENABLE_OVERLOADING)
    StringPrependCMethodInfo                ,
#endif
    stringPrependC                          ,


-- ** prependLen #method:prependLen#

#if defined(ENABLE_OVERLOADING)
    StringPrependLenMethodInfo              ,
#endif
    stringPrependLen                        ,


-- ** prependUnichar #method:prependUnichar#

#if defined(ENABLE_OVERLOADING)
    StringPrependUnicharMethodInfo          ,
#endif
    stringPrependUnichar                    ,


-- ** replace #method:replace#

#if defined(ENABLE_OVERLOADING)
    StringReplaceMethodInfo                 ,
#endif
    stringReplace                           ,


-- ** setSize #method:setSize#

#if defined(ENABLE_OVERLOADING)
    StringSetSizeMethodInfo                 ,
#endif
    stringSetSize                           ,


-- ** sizedNew #method:sizedNew#

    stringSizedNew                          ,


-- ** truncate #method:truncate#

#if defined(ENABLE_OVERLOADING)
    StringTruncateMethodInfo                ,
#endif
    stringTruncate                          ,


-- ** up #method:up#

#if defined(ENABLE_OVERLOADING)
    StringUpMethodInfo                      ,
#endif
    stringUp                                ,




 -- * Properties


-- ** allocatedLen #attr:allocatedLen#
-- | the number of bytes that can be stored in the
--   string before it needs to be reallocated. May be larger than /@len@/.

    getStringAllocatedLen                   ,
    setStringAllocatedLen                   ,
#if defined(ENABLE_OVERLOADING)
    string_allocatedLen                     ,
#endif


-- ** len #attr:len#
-- | contains the length of the string, not including the
--   terminating nul byte.

    getStringLen                            ,
    setStringLen                            ,
#if defined(ENABLE_OVERLOADING)
    string_len                              ,
#endif


-- ** str #attr:str#
-- | points to the character data. It may move as text is added.
--   The /@str@/ field is null-terminated and so
--   can be used as an ordinary C string.

    clearStringStr                          ,
    getStringStr                            ,
    setStringStr                            ,
#if defined(ENABLE_OVERLOADING)
    string_str                              ,
#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.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.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 {-# SOURCE #-} qualified GI.GLib.Structs.Bytes as GLib.Bytes

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

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

foreign import ccall "g_gstring_get_type" c_g_gstring_get_type :: 
    IO GType

type instance O.ParentTypes String = '[]
instance O.HasParentTypes String

instance B.Types.TypedObject String where
    glibType :: IO GType
glibType = IO GType
c_g_gstring_get_type

instance B.Types.GBoxed String

-- | Convert 'String' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe String) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_gstring_get_type
    gvalueSet_ :: Ptr GValue -> Maybe String -> IO ()
gvalueSet_ Ptr GValue
gv Maybe String
P.Nothing = Ptr GValue -> Ptr String -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr String
forall a. Ptr a
FP.nullPtr :: FP.Ptr String)
    gvalueSet_ Ptr GValue
gv (P.Just String
obj) = String -> (Ptr String -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr String
obj (Ptr GValue -> Ptr String -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe String)
gvalueGet_ Ptr GValue
gv = do
        Ptr String
ptr <- Ptr GValue -> IO (Ptr String)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr String)
        if Ptr String
ptr Ptr String -> Ptr String -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr String
forall a. Ptr a
FP.nullPtr
        then String -> Maybe String
forall a. a -> Maybe a
P.Just (String -> Maybe String) -> IO String -> IO (Maybe String)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr String -> String
String Ptr String
ptr
        else Maybe String -> IO (Maybe String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
forall a. Maybe a
P.Nothing
        
    

-- | Construct a `String` struct initialized to zero.
newZeroString :: MonadIO m => m String
newZeroString :: forall (m :: * -> *). MonadIO m => m String
newZeroString = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr String)
forall a. GBoxed a => Int -> IO (Ptr a)
callocBoxedBytes Int
24 IO (Ptr String) -> (Ptr String -> IO String) -> IO String
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr String -> String
String

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


-- | Get the value of the “@str@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' string #str
-- @
getStringStr :: MonadIO m => String -> m (Maybe T.Text)
getStringStr :: forall (m :: * -> *). MonadIO m => String -> m (Maybe Text)
getStringStr String
s = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ String -> (Ptr String -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr String
s ((Ptr String -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr String -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr String
ptr -> do
    CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr String
ptr Ptr String -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO CString
    Maybe Text
result <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull CString
val ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
val' -> do
        Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result

-- | Set the value of the “@str@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' string [ #str 'Data.GI.Base.Attributes.:=' value ]
-- @
setStringStr :: MonadIO m => String -> CString -> m ()
setStringStr :: forall (m :: * -> *). MonadIO m => String -> CString -> m ()
setStringStr String
s CString
val = 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
$ String -> (Ptr String -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr String
s ((Ptr String -> IO ()) -> IO ()) -> (Ptr String -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr String
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr String
ptr Ptr String -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CString
val :: CString)

-- | Set the value of the “@str@” 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' #str
-- @
clearStringStr :: MonadIO m => String -> m ()
clearStringStr :: forall (m :: * -> *). MonadIO m => String -> m ()
clearStringStr String
s = 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
$ String -> (Ptr String -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr String
s ((Ptr String -> IO ()) -> IO ()) -> (Ptr String -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr String
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr String
ptr Ptr String -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CString
forall a. Ptr a
FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING)
data StringStrFieldInfo
instance AttrInfo StringStrFieldInfo where
    type AttrBaseTypeConstraint StringStrFieldInfo = (~) String
    type AttrAllowedOps StringStrFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint StringStrFieldInfo = (~) CString
    type AttrTransferTypeConstraint StringStrFieldInfo = (~)CString
    type AttrTransferType StringStrFieldInfo = CString
    type AttrGetType StringStrFieldInfo = Maybe T.Text
    type AttrLabel StringStrFieldInfo = "str"
    type AttrOrigin StringStrFieldInfo = String
    attrGet = getStringStr
    attrSet = setStringStr
    attrConstruct = undefined
    attrClear = clearStringStr
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.String.str"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-String.html#g:attr:str"
        })

string_str :: AttrLabelProxy "str"
string_str = AttrLabelProxy

#endif


-- | Get the value of the “@len@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' string #len
-- @
getStringLen :: MonadIO m => String -> m Word64
getStringLen :: forall (m :: * -> *). MonadIO m => String -> m Word64
getStringLen String
s = IO Word64 -> m Word64
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ String -> (Ptr String -> IO Word64) -> IO Word64
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr String
s ((Ptr String -> IO Word64) -> IO Word64)
-> (Ptr String -> IO Word64) -> IO Word64
forall a b. (a -> b) -> a -> b
$ \Ptr String
ptr -> do
    Word64
val <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek (Ptr String
ptr Ptr String -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO Word64
    Word64 -> IO Word64
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
val

-- | Set the value of the “@len@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' string [ #len 'Data.GI.Base.Attributes.:=' value ]
-- @
setStringLen :: MonadIO m => String -> Word64 -> m ()
setStringLen :: forall (m :: * -> *). MonadIO m => String -> Word64 -> m ()
setStringLen String
s Word64
val = 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
$ String -> (Ptr String -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr String
s ((Ptr String -> IO ()) -> IO ()) -> (Ptr String -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr String
ptr -> do
    Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr String
ptr Ptr String -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Word64
val :: Word64)

#if defined(ENABLE_OVERLOADING)
data StringLenFieldInfo
instance AttrInfo StringLenFieldInfo where
    type AttrBaseTypeConstraint StringLenFieldInfo = (~) String
    type AttrAllowedOps StringLenFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint StringLenFieldInfo = (~) Word64
    type AttrTransferTypeConstraint StringLenFieldInfo = (~)Word64
    type AttrTransferType StringLenFieldInfo = Word64
    type AttrGetType StringLenFieldInfo = Word64
    type AttrLabel StringLenFieldInfo = "len"
    type AttrOrigin StringLenFieldInfo = String
    attrGet = getStringLen
    attrSet = setStringLen
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.String.len"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-String.html#g:attr:len"
        })

string_len :: AttrLabelProxy "len"
string_len = AttrLabelProxy

#endif


-- | Get the value of the “@allocated_len@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' string #allocatedLen
-- @
getStringAllocatedLen :: MonadIO m => String -> m Word64
getStringAllocatedLen :: forall (m :: * -> *). MonadIO m => String -> m Word64
getStringAllocatedLen String
s = IO Word64 -> m Word64
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ String -> (Ptr String -> IO Word64) -> IO Word64
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr String
s ((Ptr String -> IO Word64) -> IO Word64)
-> (Ptr String -> IO Word64) -> IO Word64
forall a b. (a -> b) -> a -> b
$ \Ptr String
ptr -> do
    Word64
val <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek (Ptr String
ptr Ptr String -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO Word64
    Word64 -> IO Word64
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
val

-- | Set the value of the “@allocated_len@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' string [ #allocatedLen 'Data.GI.Base.Attributes.:=' value ]
-- @
setStringAllocatedLen :: MonadIO m => String -> Word64 -> m ()
setStringAllocatedLen :: forall (m :: * -> *). MonadIO m => String -> Word64 -> m ()
setStringAllocatedLen String
s Word64
val = 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
$ String -> (Ptr String -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr String
s ((Ptr String -> IO ()) -> IO ()) -> (Ptr String -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr String
ptr -> do
    Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr String
ptr Ptr String -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (Word64
val :: Word64)

#if defined(ENABLE_OVERLOADING)
data StringAllocatedLenFieldInfo
instance AttrInfo StringAllocatedLenFieldInfo where
    type AttrBaseTypeConstraint StringAllocatedLenFieldInfo = (~) String
    type AttrAllowedOps StringAllocatedLenFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint StringAllocatedLenFieldInfo = (~) Word64
    type AttrTransferTypeConstraint StringAllocatedLenFieldInfo = (~)Word64
    type AttrTransferType StringAllocatedLenFieldInfo = Word64
    type AttrGetType StringAllocatedLenFieldInfo = Word64
    type AttrLabel StringAllocatedLenFieldInfo = "allocated_len"
    type AttrOrigin StringAllocatedLenFieldInfo = String
    attrGet = getStringAllocatedLen
    attrSet = setStringAllocatedLen
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.String.allocatedLen"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.27/docs/GI-GLib-Structs-String.html#g:attr:allocatedLen"
        })

string_allocatedLen :: AttrLabelProxy "allocatedLen"
string_allocatedLen = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList String
type instance O.AttributeList String = StringAttributeList
type StringAttributeList = ('[ '("str", StringStrFieldInfo), '("len", StringLenFieldInfo), '("allocatedLen", StringAllocatedLenFieldInfo)] :: [(Symbol, *)])
#endif

-- method String::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "init"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the initial text to copy into the string, or %NULL to\n  start with an empty string"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "String" })
-- throws : False
-- Skip return : False

foreign import ccall "g_string_new" g_string_new :: 
    CString ->                              -- init : TBasicType TUTF8
    IO (Ptr String)

-- | Creates a new t'GI.GLib.Structs.String.String', initialized with the given string.
stringNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Maybe (T.Text)
    -- ^ /@init@/: the initial text to copy into the string, or 'P.Nothing' to
    --   start with an empty string
    -> m String
    -- ^ __Returns:__ the new t'GI.GLib.Structs.String.String'
stringNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Maybe Text -> m String
stringNew Maybe Text
init = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    CString
maybeInit <- case Maybe Text
init of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jInit -> do
            CString
jInit' <- Text -> IO CString
textToCString Text
jInit
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jInit'
    Ptr String
result <- CString -> IO (Ptr String)
g_string_new CString
maybeInit
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringNew" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr String -> String
String) Ptr String
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeInit
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method String::new_len
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "init"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "initial contents of the string"
--                 , 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 "length of @init to use"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "String" })
-- throws : False
-- Skip return : False

foreign import ccall "g_string_new_len" g_string_new_len :: 
    CString ->                              -- init : TBasicType TUTF8
    Int64 ->                                -- len : TBasicType TInt64
    IO (Ptr String)

-- | Creates a new t'GI.GLib.Structs.String.String' with /@len@/ bytes of the /@init@/ buffer.
-- Because a length is provided, /@init@/ need not be nul-terminated,
-- and can contain embedded nul bytes.
-- 
-- Since this function does not stop at nul bytes, it is the caller\'s
-- responsibility to ensure that /@init@/ has at least /@len@/ addressable
-- bytes.
stringNewLen ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@init@/: initial contents of the string
    -> Int64
    -- ^ /@len@/: length of /@init@/ to use
    -> m String
    -- ^ __Returns:__ a new t'GI.GLib.Structs.String.String'
stringNewLen :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> Int64 -> m String
stringNewLen Text
init Int64
len = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    CString
init' <- Text -> IO CString
textToCString Text
init
    Ptr String
result <- CString -> Int64 -> IO (Ptr String)
g_string_new_len CString
init' Int64
len
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringNewLen" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr String -> String
String) Ptr String
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
init'
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method String::sized_new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "dfl_size"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the default size of the space allocated to hold the string"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "String" })
-- throws : False
-- Skip return : False

foreign import ccall "g_string_sized_new" g_string_sized_new :: 
    Word64 ->                               -- dfl_size : TBasicType TUInt64
    IO (Ptr String)

-- | Creates a new t'GI.GLib.Structs.String.String', with enough space for /@dflSize@/
-- bytes. This is useful if you are going to add a lot of
-- text to the string and don\'t want it to be reallocated
-- too often.
stringSizedNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Word64
    -- ^ /@dflSize@/: the default size of the space allocated to hold the string
    -> m String
    -- ^ __Returns:__ the new t'GI.GLib.Structs.String.String'
stringSizedNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Word64 -> m String
stringSizedNew Word64
dflSize = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
result <- Word64 -> IO (Ptr String)
g_string_sized_new Word64
dflSize
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringSizedNew" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr String -> String
String) Ptr String
result
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

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

-- | Adds a string onto the end of a t'GI.GLib.Structs.String.String', expanding
-- it if necessary.
stringAppend ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: a t'GI.GLib.Structs.String.String'
    -> T.Text
    -- ^ /@val@/: the string to append onto the end of /@string@/
    -> m String
    -- ^ __Returns:__ /@string@/
stringAppend :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> Text -> m String
stringAppend String
string Text
val = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    CString
val' <- Text -> IO CString
textToCString Text
val
    Ptr String
result <- Ptr String -> CString -> IO (Ptr String)
g_string_append Ptr String
string' CString
val'
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringAppend" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr String -> String
String) Ptr String
result
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
val'
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

#if defined(ENABLE_OVERLOADING)
data StringAppendMethodInfo
instance (signature ~ (T.Text -> m String), MonadIO m) => O.OverloadedMethod StringAppendMethodInfo String signature where
    overloadedMethod = stringAppend

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


#endif

-- method String::append_c
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "string"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GString" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "c"
--           , argType = TBasicType TInt8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the byte to append onto the end of @string"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "String" })
-- throws : False
-- Skip return : False

foreign import ccall "g_string_append_c" g_string_append_c :: 
    Ptr String ->                           -- string : TInterface (Name {namespace = "GLib", name = "String"})
    Int8 ->                                 -- c : TBasicType TInt8
    IO (Ptr String)

-- | Adds a byte onto the end of a t'GI.GLib.Structs.String.String', expanding
-- it if necessary.
stringAppendC ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: a t'GI.GLib.Structs.String.String'
    -> Int8
    -- ^ /@c@/: the byte to append onto the end of /@string@/
    -> m String
    -- ^ __Returns:__ /@string@/
stringAppendC :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> Int8 -> m String
stringAppendC String
string Int8
c = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    Ptr String
result <- Ptr String -> Int8 -> IO (Ptr String)
g_string_append_c Ptr String
string' Int8
c
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringAppendC" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr String -> String
String) Ptr String
result
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

#if defined(ENABLE_OVERLOADING)
data StringAppendCMethodInfo
instance (signature ~ (Int8 -> m String), MonadIO m) => O.OverloadedMethod StringAppendCMethodInfo String signature where
    overloadedMethod = stringAppendC

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


#endif

-- method String::append_len
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "string"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GString" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "val"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "bytes to append" , 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 @val to use, or -1 for all of @val"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "String" })
-- throws : False
-- Skip return : False

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

-- | Appends /@len@/ bytes of /@val@/ to /@string@/.
-- 
-- If /@len@/ is positive, /@val@/ may contain embedded nuls and need
-- not be nul-terminated. It is the caller\'s responsibility to
-- ensure that /@val@/ has at least /@len@/ addressable bytes.
-- 
-- If /@len@/ is negative, /@val@/ must be nul-terminated and /@len@/
-- is considered to request the entire string length. This
-- makes 'GI.GLib.Structs.String.stringAppendLen' equivalent to 'GI.GLib.Structs.String.stringAppend'.
stringAppendLen ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: a t'GI.GLib.Structs.String.String'
    -> T.Text
    -- ^ /@val@/: bytes to append
    -> Int64
    -- ^ /@len@/: number of bytes of /@val@/ to use, or -1 for all of /@val@/
    -> m String
    -- ^ __Returns:__ /@string@/
stringAppendLen :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> Text -> Int64 -> m String
stringAppendLen String
string Text
val Int64
len = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    CString
val' <- Text -> IO CString
textToCString Text
val
    Ptr String
result <- Ptr String -> CString -> Int64 -> IO (Ptr String)
g_string_append_len Ptr String
string' CString
val' Int64
len
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringAppendLen" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr String -> String
String) Ptr String
result
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
val'
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

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

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


#endif

-- method String::append_unichar
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "string"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GString" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "wc"
--           , argType = TBasicType TUniChar
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a Unicode character"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "String" })
-- throws : False
-- Skip return : False

foreign import ccall "g_string_append_unichar" g_string_append_unichar :: 
    Ptr String ->                           -- string : TInterface (Name {namespace = "GLib", name = "String"})
    CInt ->                                 -- wc : TBasicType TUniChar
    IO (Ptr String)

-- | Converts a Unicode character into UTF-8, and appends it
-- to the string.
stringAppendUnichar ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: a t'GI.GLib.Structs.String.String'
    -> Char
    -- ^ /@wc@/: a Unicode character
    -> m String
    -- ^ __Returns:__ /@string@/
stringAppendUnichar :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> Char -> m String
stringAppendUnichar String
string Char
wc = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    let wc' :: CInt
wc' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Char -> Int) -> Char -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Int
ord) Char
wc
    Ptr String
result <- Ptr String -> CInt -> IO (Ptr String)
g_string_append_unichar Ptr String
string' CInt
wc'
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringAppendUnichar" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr String -> String
String) Ptr String
result
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

#if defined(ENABLE_OVERLOADING)
data StringAppendUnicharMethodInfo
instance (signature ~ (Char -> m String), MonadIO m) => O.OverloadedMethod StringAppendUnicharMethodInfo String signature where
    overloadedMethod = stringAppendUnichar

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


#endif

-- method String::append_uri_escaped
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "string"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GString" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "unescaped"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a string" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "reserved_chars_allowed"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a string of reserved characters allowed\n    to be used, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "allow_utf8"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "set %TRUE if the escaped string may include UTF8 characters"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "String" })
-- throws : False
-- Skip return : False

foreign import ccall "g_string_append_uri_escaped" g_string_append_uri_escaped :: 
    Ptr String ->                           -- string : TInterface (Name {namespace = "GLib", name = "String"})
    CString ->                              -- unescaped : TBasicType TUTF8
    CString ->                              -- reserved_chars_allowed : TBasicType TUTF8
    CInt ->                                 -- allow_utf8 : TBasicType TBoolean
    IO (Ptr String)

-- | Appends /@unescaped@/ to /@string@/, escaping any characters that
-- are reserved in URIs using URI-style escape sequences.
-- 
-- /Since: 2.16/
stringAppendUriEscaped ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: a t'GI.GLib.Structs.String.String'
    -> T.Text
    -- ^ /@unescaped@/: a string
    -> T.Text
    -- ^ /@reservedCharsAllowed@/: a string of reserved characters allowed
    --     to be used, or 'P.Nothing'
    -> Bool
    -- ^ /@allowUtf8@/: set 'P.True' if the escaped string may include UTF8 characters
    -> m String
    -- ^ __Returns:__ /@string@/
stringAppendUriEscaped :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> Text -> Text -> Bool -> m String
stringAppendUriEscaped String
string Text
unescaped Text
reservedCharsAllowed Bool
allowUtf8 = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    CString
unescaped' <- Text -> IO CString
textToCString Text
unescaped
    CString
reservedCharsAllowed' <- Text -> IO CString
textToCString Text
reservedCharsAllowed
    let allowUtf8' :: CInt
allowUtf8' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
allowUtf8
    Ptr String
result <- Ptr String -> CString -> CString -> CInt -> IO (Ptr String)
g_string_append_uri_escaped Ptr String
string' CString
unescaped' CString
reservedCharsAllowed' CInt
allowUtf8'
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringAppendUriEscaped" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr String -> String
String) Ptr String
result
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
unescaped'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
reservedCharsAllowed'
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

#if defined(ENABLE_OVERLOADING)
data StringAppendUriEscapedMethodInfo
instance (signature ~ (T.Text -> T.Text -> Bool -> m String), MonadIO m) => O.OverloadedMethod StringAppendUriEscapedMethodInfo String signature where
    overloadedMethod = stringAppendUriEscaped

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


#endif

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

foreign import ccall "g_string_ascii_down" g_string_ascii_down :: 
    Ptr String ->                           -- string : TInterface (Name {namespace = "GLib", name = "String"})
    IO (Ptr String)

-- | Converts all uppercase ASCII letters to lowercase ASCII letters.
stringAsciiDown ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: a GString
    -> m String
    -- ^ __Returns:__ passed-in /@string@/ pointer, with all the
    --     uppercase characters converted to lowercase in place,
    --     with semantics that exactly match 'GI.GLib.Functions.asciiTolower'.
stringAsciiDown :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> m String
stringAsciiDown String
string = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    Ptr String
result <- Ptr String -> IO (Ptr String)
g_string_ascii_down Ptr String
string'
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringAsciiDown" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr String -> String
String) Ptr String
result
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

#if defined(ENABLE_OVERLOADING)
data StringAsciiDownMethodInfo
instance (signature ~ (m String), MonadIO m) => O.OverloadedMethod StringAsciiDownMethodInfo String signature where
    overloadedMethod = stringAsciiDown

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


#endif

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

foreign import ccall "g_string_ascii_up" g_string_ascii_up :: 
    Ptr String ->                           -- string : TInterface (Name {namespace = "GLib", name = "String"})
    IO (Ptr String)

-- | Converts all lowercase ASCII letters to uppercase ASCII letters.
stringAsciiUp ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: a GString
    -> m String
    -- ^ __Returns:__ passed-in /@string@/ pointer, with all the
    --     lowercase characters converted to uppercase in place,
    --     with semantics that exactly match 'GI.GLib.Functions.asciiToupper'.
stringAsciiUp :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> m String
stringAsciiUp String
string = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    Ptr String
result <- Ptr String -> IO (Ptr String)
g_string_ascii_up Ptr String
string'
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringAsciiUp" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr String -> String
String) Ptr String
result
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

#if defined(ENABLE_OVERLOADING)
data StringAsciiUpMethodInfo
instance (signature ~ (m String), MonadIO m) => O.OverloadedMethod StringAsciiUpMethodInfo String signature where
    overloadedMethod = stringAsciiUp

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


#endif

-- method String::assign
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "string"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the destination #GString. Its current contents\n         are destroyed."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "rval"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the string to copy into @string"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "String" })
-- throws : False
-- Skip return : False

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

-- | Copies the bytes from a string into a t'GI.GLib.Structs.String.String',
-- destroying any previous contents. It is rather like
-- the standard @/strcpy()/@ function, except that you do not
-- have to worry about having enough space to copy the string.
stringAssign ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: the destination t'GI.GLib.Structs.String.String'. Its current contents
    --          are destroyed.
    -> T.Text
    -- ^ /@rval@/: the string to copy into /@string@/
    -> m String
    -- ^ __Returns:__ /@string@/
stringAssign :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> Text -> m String
stringAssign String
string Text
rval = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    CString
rval' <- Text -> IO CString
textToCString Text
rval
    Ptr String
result <- Ptr String -> CString -> IO (Ptr String)
g_string_assign Ptr String
string' CString
rval'
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringAssign" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr String -> String
String) Ptr String
result
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
rval'
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

#if defined(ENABLE_OVERLOADING)
data StringAssignMethodInfo
instance (signature ~ (T.Text -> m String), MonadIO m) => O.OverloadedMethod StringAssignMethodInfo String signature where
    overloadedMethod = stringAssign

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


#endif

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

foreign import ccall "g_string_down" g_string_down :: 
    Ptr String ->                           -- string : TInterface (Name {namespace = "GLib", name = "String"})
    IO (Ptr String)

{-# DEPRECATED stringDown ["(Since version 2.2)","This function uses the locale-specific","    @/tolower()/@ function, which is almost never the right thing.","    Use 'GI.GLib.Structs.String.stringAsciiDown' or 'GI.GLib.Functions.utf8Strdown' instead."] #-}
-- | Converts a t'GI.GLib.Structs.String.String' to lowercase.
stringDown ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: a t'GI.GLib.Structs.String.String'
    -> m String
    -- ^ __Returns:__ the t'GI.GLib.Structs.String.String'
stringDown :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> m String
stringDown String
string = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    Ptr String
result <- Ptr String -> IO (Ptr String)
g_string_down Ptr String
string'
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringDown" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr String -> String
String) Ptr String
result
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

#if defined(ENABLE_OVERLOADING)
data StringDownMethodInfo
instance (signature ~ (m String), MonadIO m) => O.OverloadedMethod StringDownMethodInfo String signature where
    overloadedMethod = stringDown

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


#endif

-- method String::equal
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "v"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GString" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "v2"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "another #GString" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_string_equal" g_string_equal :: 
    Ptr String ->                           -- v : TInterface (Name {namespace = "GLib", name = "String"})
    Ptr String ->                           -- v2 : TInterface (Name {namespace = "GLib", name = "String"})
    IO CInt

-- | Compares two strings for equality, returning 'P.True' if they are equal.
-- For use with t'GI.GLib.Structs.HashTable.HashTable'.
stringEqual ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@v@/: a t'GI.GLib.Structs.String.String'
    -> String
    -- ^ /@v2@/: another t'GI.GLib.Structs.String.String'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the strings are the same length and contain the
    --     same bytes
stringEqual :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> String -> m Bool
stringEqual String
v String
v2 = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
v' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
v
    Ptr String
v2' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
v2
    CInt
result <- Ptr String -> Ptr String -> IO CInt
g_string_equal Ptr String
v' Ptr String
v2'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
v
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
v2
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data StringEqualMethodInfo
instance (signature ~ (String -> m Bool), MonadIO m) => O.OverloadedMethod StringEqualMethodInfo String signature where
    overloadedMethod = stringEqual

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


#endif

-- method String::erase
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "string"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GString" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the position of the content to remove"
--                 , 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
--                       "the number of bytes to remove, or -1 to remove all\n      following bytes"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "String" })
-- throws : False
-- Skip return : False

foreign import ccall "g_string_erase" g_string_erase :: 
    Ptr String ->                           -- string : TInterface (Name {namespace = "GLib", name = "String"})
    Int64 ->                                -- pos : TBasicType TInt64
    Int64 ->                                -- len : TBasicType TInt64
    IO (Ptr String)

-- | Removes /@len@/ bytes from a t'GI.GLib.Structs.String.String', starting at position /@pos@/.
-- The rest of the t'GI.GLib.Structs.String.String' is shifted down to fill the gap.
stringErase ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: a t'GI.GLib.Structs.String.String'
    -> Int64
    -- ^ /@pos@/: the position of the content to remove
    -> Int64
    -- ^ /@len@/: the number of bytes to remove, or -1 to remove all
    --       following bytes
    -> m String
    -- ^ __Returns:__ /@string@/
stringErase :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> Int64 -> Int64 -> m String
stringErase String
string Int64
pos Int64
len = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    Ptr String
result <- Ptr String -> Int64 -> Int64 -> IO (Ptr String)
g_string_erase Ptr String
string' Int64
pos Int64
len
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringErase" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr String -> String
String) Ptr String
result
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

#if defined(ENABLE_OVERLOADING)
data StringEraseMethodInfo
instance (signature ~ (Int64 -> Int64 -> m String), MonadIO m) => O.OverloadedMethod StringEraseMethodInfo String signature where
    overloadedMethod = stringErase

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


#endif

-- method String::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "string"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GString" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "free_segment"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "if %TRUE, the actual character data is freed as well"
--                 , 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_free" g_string_free :: 
    Ptr String ->                           -- string : TInterface (Name {namespace = "GLib", name = "String"})
    CInt ->                                 -- free_segment : TBasicType TBoolean
    IO CString

-- | Frees the memory allocated for the t'GI.GLib.Structs.String.String'.
-- If /@freeSegment@/ is 'P.True' it also frees the character data.  If
-- it\'s 'P.False', the caller gains ownership of the buffer and must
-- free it after use with 'GI.GLib.Functions.free'.
stringFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: a t'GI.GLib.Structs.String.String'
    -> Bool
    -- ^ /@freeSegment@/: if 'P.True', the actual character data is freed as well
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the character data of /@string@/
    --          (i.e. 'P.Nothing' if /@freeSegment@/ is 'P.True')
stringFree :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> Bool -> m (Maybe Text)
stringFree String
string Bool
freeSegment = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed String
string
    let freeSegment' :: CInt
freeSegment' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
freeSegment
    CString
result <- Ptr String -> CInt -> IO CString
g_string_free Ptr String
string' CInt
freeSegment'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data StringFreeMethodInfo
instance (signature ~ (Bool -> m (Maybe T.Text)), MonadIO m) => O.OverloadedMethod StringFreeMethodInfo String signature where
    overloadedMethod = stringFree

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


#endif

-- method String::free_to_bytes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "string"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GString" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "Bytes" })
-- throws : False
-- Skip return : False

foreign import ccall "g_string_free_to_bytes" g_string_free_to_bytes :: 
    Ptr String ->                           -- string : TInterface (Name {namespace = "GLib", name = "String"})
    IO (Ptr GLib.Bytes.Bytes)

-- | Transfers ownership of the contents of /@string@/ to a newly allocated
-- t'GI.GLib.Structs.Bytes.Bytes'.  The t'GI.GLib.Structs.String.String' structure itself is deallocated, and it is
-- therefore invalid to use /@string@/ after invoking this function.
-- 
-- Note that while t'GI.GLib.Structs.String.String' ensures that its buffer always has a
-- trailing nul character (not reflected in its \"len\"), the returned
-- t'GI.GLib.Structs.Bytes.Bytes' does not include this extra nul; i.e. it has length exactly
-- equal to the \"len\" member.
-- 
-- /Since: 2.34/
stringFreeToBytes ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: a t'GI.GLib.Structs.String.String'
    -> m GLib.Bytes.Bytes
    -- ^ __Returns:__ A newly allocated t'GI.GLib.Structs.Bytes.Bytes' containing contents of /@string@/; /@string@/ itself is freed
stringFreeToBytes :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> m Bytes
stringFreeToBytes String
string = IO Bytes -> m Bytes
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bytes -> m Bytes) -> IO Bytes -> m Bytes
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed String
string
    Ptr Bytes
result <- Ptr String -> IO (Ptr Bytes)
g_string_free_to_bytes Ptr String
string'
    Text -> Ptr Bytes -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringFreeToBytes" Ptr Bytes
result
    Bytes
result' <- ((ManagedPtr Bytes -> Bytes) -> Ptr Bytes -> IO Bytes
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Bytes -> Bytes
GLib.Bytes.Bytes) Ptr Bytes
result
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    Bytes -> IO Bytes
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bytes
result'

#if defined(ENABLE_OVERLOADING)
data StringFreeToBytesMethodInfo
instance (signature ~ (m GLib.Bytes.Bytes), MonadIO m) => O.OverloadedMethod StringFreeToBytesMethodInfo String signature where
    overloadedMethod = stringFreeToBytes

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


#endif

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

foreign import ccall "g_string_hash" g_string_hash :: 
    Ptr String ->                           -- str : TInterface (Name {namespace = "GLib", name = "String"})
    IO Word32

-- | Creates a hash code for /@str@/; for use with t'GI.GLib.Structs.HashTable.HashTable'.
stringHash ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@str@/: a string to hash
    -> m Word32
    -- ^ __Returns:__ hash code for /@str@/
stringHash :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> m Word32
stringHash String
str = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
str' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
str
    Word32
result <- Ptr String -> IO Word32
g_string_hash Ptr String
str'
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
str
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data StringHashMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.OverloadedMethod StringHashMethodInfo String signature where
    overloadedMethod = stringHash

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


#endif

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

foreign import ccall "g_string_insert" g_string_insert :: 
    Ptr String ->                           -- string : TInterface (Name {namespace = "GLib", name = "String"})
    Int64 ->                                -- pos : TBasicType TInt64
    CString ->                              -- val : TBasicType TUTF8
    IO (Ptr String)

-- | Inserts a copy of a string into a t'GI.GLib.Structs.String.String',
-- expanding it if necessary.
stringInsert ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: a t'GI.GLib.Structs.String.String'
    -> Int64
    -- ^ /@pos@/: the position to insert the copy of the string
    -> T.Text
    -- ^ /@val@/: the string to insert
    -> m String
    -- ^ __Returns:__ /@string@/
stringInsert :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> Int64 -> Text -> m String
stringInsert String
string Int64
pos Text
val = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    CString
val' <- Text -> IO CString
textToCString Text
val
    Ptr String
result <- Ptr String -> Int64 -> CString -> IO (Ptr String)
g_string_insert Ptr String
string' Int64
pos CString
val'
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringInsert" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr String -> String
String) Ptr String
result
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
val'
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

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

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


#endif

-- method String::insert_c
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "string"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GString" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the position to insert the byte"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "c"
--           , argType = TBasicType TInt8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the byte to insert" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "String" })
-- throws : False
-- Skip return : False

foreign import ccall "g_string_insert_c" g_string_insert_c :: 
    Ptr String ->                           -- string : TInterface (Name {namespace = "GLib", name = "String"})
    Int64 ->                                -- pos : TBasicType TInt64
    Int8 ->                                 -- c : TBasicType TInt8
    IO (Ptr String)

-- | Inserts a byte into a t'GI.GLib.Structs.String.String', expanding it if necessary.
stringInsertC ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: a t'GI.GLib.Structs.String.String'
    -> Int64
    -- ^ /@pos@/: the position to insert the byte
    -> Int8
    -- ^ /@c@/: the byte to insert
    -> m String
    -- ^ __Returns:__ /@string@/
stringInsertC :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> Int64 -> Int8 -> m String
stringInsertC String
string Int64
pos Int8
c = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    Ptr String
result <- Ptr String -> Int64 -> Int8 -> IO (Ptr String)
g_string_insert_c Ptr String
string' Int64
pos Int8
c
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringInsertC" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr String -> String
String) Ptr String
result
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

#if defined(ENABLE_OVERLOADING)
data StringInsertCMethodInfo
instance (signature ~ (Int64 -> Int8 -> m String), MonadIO m) => O.OverloadedMethod StringInsertCMethodInfo String signature where
    overloadedMethod = stringInsertC

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


#endif

-- method String::insert_len
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "string"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GString" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "position in @string where insertion should\n      happen, or -1 for at the end"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "val"
--           , 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 @val to insert, or -1 for all of @val"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "String" })
-- throws : False
-- Skip return : False

foreign import ccall "g_string_insert_len" g_string_insert_len :: 
    Ptr String ->                           -- string : TInterface (Name {namespace = "GLib", name = "String"})
    Int64 ->                                -- pos : TBasicType TInt64
    CString ->                              -- val : TBasicType TUTF8
    Int64 ->                                -- len : TBasicType TInt64
    IO (Ptr String)

-- | Inserts /@len@/ bytes of /@val@/ into /@string@/ at /@pos@/.
-- 
-- If /@len@/ is positive, /@val@/ may contain embedded nuls and need
-- not be nul-terminated. It is the caller\'s responsibility to
-- ensure that /@val@/ has at least /@len@/ addressable bytes.
-- 
-- If /@len@/ is negative, /@val@/ must be nul-terminated and /@len@/
-- is considered to request the entire string length.
-- 
-- If /@pos@/ is -1, bytes are inserted at the end of the string.
stringInsertLen ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: a t'GI.GLib.Structs.String.String'
    -> Int64
    -- ^ /@pos@/: position in /@string@/ where insertion should
    --       happen, or -1 for at the end
    -> T.Text
    -- ^ /@val@/: bytes to insert
    -> Int64
    -- ^ /@len@/: number of bytes of /@val@/ to insert, or -1 for all of /@val@/
    -> m String
    -- ^ __Returns:__ /@string@/
stringInsertLen :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> Int64 -> Text -> Int64 -> m String
stringInsertLen String
string Int64
pos Text
val Int64
len = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    CString
val' <- Text -> IO CString
textToCString Text
val
    Ptr String
result <- Ptr String -> Int64 -> CString -> Int64 -> IO (Ptr String)
g_string_insert_len Ptr String
string' Int64
pos CString
val' Int64
len
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringInsertLen" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr String -> String
String) Ptr String
result
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
val'
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

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

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


#endif

-- method String::insert_unichar
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "string"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GString" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the position at which to insert character, or -1\n    to append at the end of the string"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "wc"
--           , argType = TBasicType TUniChar
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a Unicode character"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "String" })
-- throws : False
-- Skip return : False

foreign import ccall "g_string_insert_unichar" g_string_insert_unichar :: 
    Ptr String ->                           -- string : TInterface (Name {namespace = "GLib", name = "String"})
    Int64 ->                                -- pos : TBasicType TInt64
    CInt ->                                 -- wc : TBasicType TUniChar
    IO (Ptr String)

-- | Converts a Unicode character into UTF-8, and insert it
-- into the string at the given position.
stringInsertUnichar ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: a t'GI.GLib.Structs.String.String'
    -> Int64
    -- ^ /@pos@/: the position at which to insert character, or -1
    --     to append at the end of the string
    -> Char
    -- ^ /@wc@/: a Unicode character
    -> m String
    -- ^ __Returns:__ /@string@/
stringInsertUnichar :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> Int64 -> Char -> m String
stringInsertUnichar String
string Int64
pos Char
wc = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    let wc' :: CInt
wc' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Char -> Int) -> Char -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Int
ord) Char
wc
    Ptr String
result <- Ptr String -> Int64 -> CInt -> IO (Ptr String)
g_string_insert_unichar Ptr String
string' Int64
pos CInt
wc'
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringInsertUnichar" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr String -> String
String) Ptr String
result
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

#if defined(ENABLE_OVERLOADING)
data StringInsertUnicharMethodInfo
instance (signature ~ (Int64 -> Char -> m String), MonadIO m) => O.OverloadedMethod StringInsertUnicharMethodInfo String signature where
    overloadedMethod = stringInsertUnichar

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


#endif

-- method String::overwrite
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "string"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GString" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the position at which to start overwriting"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "val"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the string that will overwrite the @string starting at @pos"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "String" })
-- throws : False
-- Skip return : False

foreign import ccall "g_string_overwrite" g_string_overwrite :: 
    Ptr String ->                           -- string : TInterface (Name {namespace = "GLib", name = "String"})
    Word64 ->                               -- pos : TBasicType TUInt64
    CString ->                              -- val : TBasicType TUTF8
    IO (Ptr String)

-- | Overwrites part of a string, lengthening it if necessary.
-- 
-- /Since: 2.14/
stringOverwrite ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: a t'GI.GLib.Structs.String.String'
    -> Word64
    -- ^ /@pos@/: the position at which to start overwriting
    -> T.Text
    -- ^ /@val@/: the string that will overwrite the /@string@/ starting at /@pos@/
    -> m String
    -- ^ __Returns:__ /@string@/
stringOverwrite :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> Word64 -> Text -> m String
stringOverwrite String
string Word64
pos Text
val = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    CString
val' <- Text -> IO CString
textToCString Text
val
    Ptr String
result <- Ptr String -> Word64 -> CString -> IO (Ptr String)
g_string_overwrite Ptr String
string' Word64
pos CString
val'
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringOverwrite" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr String -> String
String) Ptr String
result
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
val'
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

#if defined(ENABLE_OVERLOADING)
data StringOverwriteMethodInfo
instance (signature ~ (Word64 -> T.Text -> m String), MonadIO m) => O.OverloadedMethod StringOverwriteMethodInfo String signature where
    overloadedMethod = stringOverwrite

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


#endif

-- method String::overwrite_len
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "string"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GString" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the position at which to start overwriting"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "val"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the string that will overwrite the @string starting at @pos"
--                 , 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 "the number of bytes to write from @val"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "String" })
-- throws : False
-- Skip return : False

foreign import ccall "g_string_overwrite_len" g_string_overwrite_len :: 
    Ptr String ->                           -- string : TInterface (Name {namespace = "GLib", name = "String"})
    Word64 ->                               -- pos : TBasicType TUInt64
    CString ->                              -- val : TBasicType TUTF8
    Int64 ->                                -- len : TBasicType TInt64
    IO (Ptr String)

-- | Overwrites part of a string, lengthening it if necessary.
-- This function will work with embedded nuls.
-- 
-- /Since: 2.14/
stringOverwriteLen ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: a t'GI.GLib.Structs.String.String'
    -> Word64
    -- ^ /@pos@/: the position at which to start overwriting
    -> T.Text
    -- ^ /@val@/: the string that will overwrite the /@string@/ starting at /@pos@/
    -> Int64
    -- ^ /@len@/: the number of bytes to write from /@val@/
    -> m String
    -- ^ __Returns:__ /@string@/
stringOverwriteLen :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> Word64 -> Text -> Int64 -> m String
stringOverwriteLen String
string Word64
pos Text
val Int64
len = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    CString
val' <- Text -> IO CString
textToCString Text
val
    Ptr String
result <- Ptr String -> Word64 -> CString -> Int64 -> IO (Ptr String)
g_string_overwrite_len Ptr String
string' Word64
pos CString
val' Int64
len
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringOverwriteLen" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr String -> String
String) Ptr String
result
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
val'
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

#if defined(ENABLE_OVERLOADING)
data StringOverwriteLenMethodInfo
instance (signature ~ (Word64 -> T.Text -> Int64 -> m String), MonadIO m) => O.OverloadedMethod StringOverwriteLenMethodInfo String signature where
    overloadedMethod = stringOverwriteLen

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


#endif

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

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

-- | Adds a string on to the start of a t'GI.GLib.Structs.String.String',
-- expanding it if necessary.
stringPrepend ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: a t'GI.GLib.Structs.String.String'
    -> T.Text
    -- ^ /@val@/: the string to prepend on the start of /@string@/
    -> m String
    -- ^ __Returns:__ /@string@/
stringPrepend :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> Text -> m String
stringPrepend String
string Text
val = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    CString
val' <- Text -> IO CString
textToCString Text
val
    Ptr String
result <- Ptr String -> CString -> IO (Ptr String)
g_string_prepend Ptr String
string' CString
val'
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringPrepend" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr String -> String
String) Ptr String
result
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
val'
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

#if defined(ENABLE_OVERLOADING)
data StringPrependMethodInfo
instance (signature ~ (T.Text -> m String), MonadIO m) => O.OverloadedMethod StringPrependMethodInfo String signature where
    overloadedMethod = stringPrepend

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


#endif

-- method String::prepend_c
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "string"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GString" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "c"
--           , argType = TBasicType TInt8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the byte to prepend on the start of the #GString"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "String" })
-- throws : False
-- Skip return : False

foreign import ccall "g_string_prepend_c" g_string_prepend_c :: 
    Ptr String ->                           -- string : TInterface (Name {namespace = "GLib", name = "String"})
    Int8 ->                                 -- c : TBasicType TInt8
    IO (Ptr String)

-- | Adds a byte onto the start of a t'GI.GLib.Structs.String.String',
-- expanding it if necessary.
stringPrependC ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: a t'GI.GLib.Structs.String.String'
    -> Int8
    -- ^ /@c@/: the byte to prepend on the start of the t'GI.GLib.Structs.String.String'
    -> m String
    -- ^ __Returns:__ /@string@/
stringPrependC :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> Int8 -> m String
stringPrependC String
string Int8
c = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    Ptr String
result <- Ptr String -> Int8 -> IO (Ptr String)
g_string_prepend_c Ptr String
string' Int8
c
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringPrependC" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr String -> String
String) Ptr String
result
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

#if defined(ENABLE_OVERLOADING)
data StringPrependCMethodInfo
instance (signature ~ (Int8 -> m String), MonadIO m) => O.OverloadedMethod StringPrependCMethodInfo String signature where
    overloadedMethod = stringPrependC

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


#endif

-- method String::prepend_len
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "string"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GString" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "val"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "bytes to prepend" , 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 in @val to prepend, or -1 for all of @val"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "String" })
-- throws : False
-- Skip return : False

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

-- | Prepends /@len@/ bytes of /@val@/ to /@string@/.
-- 
-- If /@len@/ is positive, /@val@/ may contain embedded nuls and need
-- not be nul-terminated. It is the caller\'s responsibility to
-- ensure that /@val@/ has at least /@len@/ addressable bytes.
-- 
-- If /@len@/ is negative, /@val@/ must be nul-terminated and /@len@/
-- is considered to request the entire string length. This
-- makes 'GI.GLib.Structs.String.stringPrependLen' equivalent to 'GI.GLib.Structs.String.stringPrepend'.
stringPrependLen ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: a t'GI.GLib.Structs.String.String'
    -> T.Text
    -- ^ /@val@/: bytes to prepend
    -> Int64
    -- ^ /@len@/: number of bytes in /@val@/ to prepend, or -1 for all of /@val@/
    -> m String
    -- ^ __Returns:__ /@string@/
stringPrependLen :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> Text -> Int64 -> m String
stringPrependLen String
string Text
val Int64
len = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    CString
val' <- Text -> IO CString
textToCString Text
val
    Ptr String
result <- Ptr String -> CString -> Int64 -> IO (Ptr String)
g_string_prepend_len Ptr String
string' CString
val' Int64
len
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringPrependLen" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr String -> String
String) Ptr String
result
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
val'
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

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

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


#endif

-- method String::prepend_unichar
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "string"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GString" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "wc"
--           , argType = TBasicType TUniChar
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a Unicode character"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "String" })
-- throws : False
-- Skip return : False

foreign import ccall "g_string_prepend_unichar" g_string_prepend_unichar :: 
    Ptr String ->                           -- string : TInterface (Name {namespace = "GLib", name = "String"})
    CInt ->                                 -- wc : TBasicType TUniChar
    IO (Ptr String)

-- | Converts a Unicode character into UTF-8, and prepends it
-- to the string.
stringPrependUnichar ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: a t'GI.GLib.Structs.String.String'
    -> Char
    -- ^ /@wc@/: a Unicode character
    -> m String
    -- ^ __Returns:__ /@string@/
stringPrependUnichar :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> Char -> m String
stringPrependUnichar String
string Char
wc = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    let wc' :: CInt
wc' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Char -> Int) -> Char -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Int
ord) Char
wc
    Ptr String
result <- Ptr String -> CInt -> IO (Ptr String)
g_string_prepend_unichar Ptr String
string' CInt
wc'
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringPrependUnichar" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr String -> String
String) Ptr String
result
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

#if defined(ENABLE_OVERLOADING)
data StringPrependUnicharMethodInfo
instance (signature ~ (Char -> m String), MonadIO m) => O.OverloadedMethod StringPrependUnicharMethodInfo String signature where
    overloadedMethod = stringPrependUnichar

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


#endif

-- method String::replace
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "string"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GString" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "find"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the string to find in @string"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "replace"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the string to insert in place of @find"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "limit"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the maximum instances of @find to replace with @replace, or `0` for\nno limit"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_string_replace" g_string_replace :: 
    Ptr String ->                           -- string : TInterface (Name {namespace = "GLib", name = "String"})
    CString ->                              -- find : TBasicType TUTF8
    CString ->                              -- replace : TBasicType TUTF8
    Word32 ->                               -- limit : TBasicType TUInt
    IO Word32

-- | Replaces the string /@find@/ with the string /@replace@/ in a t'GI.GLib.Structs.String.String' up to
-- /@limit@/ times. If the number of instances of /@find@/ in the t'GI.GLib.Structs.String.String' is
-- less than /@limit@/, all instances are replaced. If /@limit@/ is @0@,
-- all instances of /@find@/ are replaced.
-- 
-- If /@find@/ is the empty string, since versions 2.69.1 and 2.68.4 the
-- replacement will be inserted no more than once per possible position
-- (beginning of string, end of string and between characters). This did
-- not work correctly in earlier versions.
-- 
-- /Since: 2.68/
stringReplace ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: a t'GI.GLib.Structs.String.String'
    -> T.Text
    -- ^ /@find@/: the string to find in /@string@/
    -> T.Text
    -- ^ /@replace@/: the string to insert in place of /@find@/
    -> Word32
    -- ^ /@limit@/: the maximum instances of /@find@/ to replace with /@replace@/, or @0@ for
    -- no limit
    -> m Word32
    -- ^ __Returns:__ the number of find and replace operations performed.
stringReplace :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> Text -> Text -> Word32 -> m Word32
stringReplace String
string Text
find Text
replace Word32
limit = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    CString
find' <- Text -> IO CString
textToCString Text
find
    CString
replace' <- Text -> IO CString
textToCString Text
replace
    Word32
result <- Ptr String -> CString -> CString -> Word32 -> IO Word32
g_string_replace Ptr String
string' CString
find' CString
replace' Word32
limit
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
find'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
replace'
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data StringReplaceMethodInfo
instance (signature ~ (T.Text -> T.Text -> Word32 -> m Word32), MonadIO m) => O.OverloadedMethod StringReplaceMethodInfo String signature where
    overloadedMethod = stringReplace

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


#endif

-- method String::set_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "string"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GString" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "len"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new length" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "String" })
-- throws : False
-- Skip return : False

foreign import ccall "g_string_set_size" g_string_set_size :: 
    Ptr String ->                           -- string : TInterface (Name {namespace = "GLib", name = "String"})
    Word64 ->                               -- len : TBasicType TUInt64
    IO (Ptr String)

-- | Sets the length of a t'GI.GLib.Structs.String.String'. If the length is less than
-- the current length, the string will be truncated. If the
-- length is greater than the current length, the contents
-- of the newly added area are undefined. (However, as
-- always, string->str[string->len] will be a nul byte.)
stringSetSize ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: a t'GI.GLib.Structs.String.String'
    -> Word64
    -- ^ /@len@/: the new length
    -> m String
    -- ^ __Returns:__ /@string@/
stringSetSize :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> Word64 -> m String
stringSetSize String
string Word64
len = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    Ptr String
result <- Ptr String -> Word64 -> IO (Ptr String)
g_string_set_size Ptr String
string' Word64
len
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringSetSize" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr String -> String
String) Ptr String
result
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

#if defined(ENABLE_OVERLOADING)
data StringSetSizeMethodInfo
instance (signature ~ (Word64 -> m String), MonadIO m) => O.OverloadedMethod StringSetSizeMethodInfo String signature where
    overloadedMethod = stringSetSize

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


#endif

-- method String::truncate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "string"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GString" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "len"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new size of @string"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "String" })
-- throws : False
-- Skip return : False

foreign import ccall "g_string_truncate" g_string_truncate :: 
    Ptr String ->                           -- string : TInterface (Name {namespace = "GLib", name = "String"})
    Word64 ->                               -- len : TBasicType TUInt64
    IO (Ptr String)

-- | Cuts off the end of the GString, leaving the first /@len@/ bytes.
stringTruncate ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: a t'GI.GLib.Structs.String.String'
    -> Word64
    -- ^ /@len@/: the new size of /@string@/
    -> m String
    -- ^ __Returns:__ /@string@/
stringTruncate :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> Word64 -> m String
stringTruncate String
string Word64
len = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    Ptr String
result <- Ptr String -> Word64 -> IO (Ptr String)
g_string_truncate Ptr String
string' Word64
len
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringTruncate" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr String -> String
String) Ptr String
result
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

#if defined(ENABLE_OVERLOADING)
data StringTruncateMethodInfo
instance (signature ~ (Word64 -> m String), MonadIO m) => O.OverloadedMethod StringTruncateMethodInfo String signature where
    overloadedMethod = stringTruncate

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


#endif

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

foreign import ccall "g_string_up" g_string_up :: 
    Ptr String ->                           -- string : TInterface (Name {namespace = "GLib", name = "String"})
    IO (Ptr String)

{-# DEPRECATED stringUp ["(Since version 2.2)","This function uses the locale-specific","    @/toupper()/@ function, which is almost never the right thing.","    Use 'GI.GLib.Structs.String.stringAsciiUp' or 'GI.GLib.Functions.utf8Strup' instead."] #-}
-- | Converts a t'GI.GLib.Structs.String.String' to uppercase.
stringUp ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    String
    -- ^ /@string@/: a t'GI.GLib.Structs.String.String'
    -> m String
    -- ^ __Returns:__ /@string@/
stringUp :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> m String
stringUp String
string = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    Ptr String
string' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
string
    Ptr String
result <- Ptr String -> IO (Ptr String)
g_string_up Ptr String
string'
    Text -> Ptr String -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringUp" Ptr String
result
    String
result' <- ((ManagedPtr String -> String) -> Ptr String -> IO String
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr String -> String
String) Ptr String
result
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
string
    String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

#if defined(ENABLE_OVERLOADING)
data StringUpMethodInfo
instance (signature ~ (m String), MonadIO m) => O.OverloadedMethod StringUpMethodInfo String signature where
    overloadedMethod = stringUp

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


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveStringMethod (t :: Symbol) (o :: *) :: * where
    ResolveStringMethod "append" o = StringAppendMethodInfo
    ResolveStringMethod "appendC" o = StringAppendCMethodInfo
    ResolveStringMethod "appendLen" o = StringAppendLenMethodInfo
    ResolveStringMethod "appendUnichar" o = StringAppendUnicharMethodInfo
    ResolveStringMethod "appendUriEscaped" o = StringAppendUriEscapedMethodInfo
    ResolveStringMethod "asciiDown" o = StringAsciiDownMethodInfo
    ResolveStringMethod "asciiUp" o = StringAsciiUpMethodInfo
    ResolveStringMethod "assign" o = StringAssignMethodInfo
    ResolveStringMethod "down" o = StringDownMethodInfo
    ResolveStringMethod "equal" o = StringEqualMethodInfo
    ResolveStringMethod "erase" o = StringEraseMethodInfo
    ResolveStringMethod "free" o = StringFreeMethodInfo
    ResolveStringMethod "freeToBytes" o = StringFreeToBytesMethodInfo
    ResolveStringMethod "hash" o = StringHashMethodInfo
    ResolveStringMethod "insert" o = StringInsertMethodInfo
    ResolveStringMethod "insertC" o = StringInsertCMethodInfo
    ResolveStringMethod "insertLen" o = StringInsertLenMethodInfo
    ResolveStringMethod "insertUnichar" o = StringInsertUnicharMethodInfo
    ResolveStringMethod "overwrite" o = StringOverwriteMethodInfo
    ResolveStringMethod "overwriteLen" o = StringOverwriteLenMethodInfo
    ResolveStringMethod "prepend" o = StringPrependMethodInfo
    ResolveStringMethod "prependC" o = StringPrependCMethodInfo
    ResolveStringMethod "prependLen" o = StringPrependLenMethodInfo
    ResolveStringMethod "prependUnichar" o = StringPrependUnicharMethodInfo
    ResolveStringMethod "replace" o = StringReplaceMethodInfo
    ResolveStringMethod "truncate" o = StringTruncateMethodInfo
    ResolveStringMethod "up" o = StringUpMethodInfo
    ResolveStringMethod "setSize" o = StringSetSizeMethodInfo
    ResolveStringMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif