{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @GtkStringList@ is a list model that wraps an array of strings.
-- 
-- The objects in the model have a \"string\" property.
-- 
-- @GtkStringList@ is well-suited for any place where you would
-- typically use a @char*[]@, but need a list model.
-- 
-- = GtkStringList as GtkBuildable
-- 
-- The @GtkStringList@ implementation of the @GtkBuildable@ interface
-- supports adding items directly using the \<items> element and
-- specifying \<item> elements for each item. Each \<item> element
-- supports the regular translation attributes “translatable”,
-- “context” and “comments”.
-- 
-- Here is a UI definition fragment specifying a @GtkStringList@
-- 
-- 
-- === /xml code/
-- ><object class="GtkStringList">
-- >  <items>
-- >    <item translatable="yes">Factory</item>
-- >    <item translatable="yes">Home</item>
-- >    <item translatable="yes">Subway</item>
-- >  </items>
-- ></object>
-- 

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

module GI.Gtk.Objects.StringList
    ( 

-- * Exported types
    StringList(..)                          ,
    IsStringList                            ,
    toStringList                            ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [append]("GI.Gtk.Objects.StringList#g:method:append"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [itemsChanged]("GI.Gio.Interfaces.ListModel#g:method:itemsChanged"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [remove]("GI.Gtk.Objects.StringList#g:method:remove"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [splice]("GI.Gtk.Objects.StringList#g:method:splice"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [take]("GI.Gtk.Objects.StringList#g:method:take"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getBuildableId]("GI.Gtk.Interfaces.Buildable#g:method:getBuildableId"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getItem]("GI.Gio.Interfaces.ListModel#g:method:getItem"), [getItemType]("GI.Gio.Interfaces.ListModel#g:method:getItemType"), [getNItems]("GI.Gio.Interfaces.ListModel#g:method:getNItems"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getString]("GI.Gtk.Objects.StringList#g:method:getString").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveStringListMethod                 ,
#endif

-- ** append #method:append#

#if defined(ENABLE_OVERLOADING)
    StringListAppendMethodInfo              ,
#endif
    stringListAppend                        ,


-- ** getString #method:getString#

#if defined(ENABLE_OVERLOADING)
    StringListGetStringMethodInfo           ,
#endif
    stringListGetString                     ,


-- ** new #method:new#

    stringListNew                           ,


-- ** remove #method:remove#

#if defined(ENABLE_OVERLOADING)
    StringListRemoveMethodInfo              ,
#endif
    stringListRemove                        ,


-- ** splice #method:splice#

#if defined(ENABLE_OVERLOADING)
    StringListSpliceMethodInfo              ,
#endif
    stringListSplice                        ,


-- ** take #method:take#

#if defined(ENABLE_OVERLOADING)
    StringListTakeMethodInfo                ,
#endif
    stringListTake                          ,




    ) 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 qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Interfaces.ListModel as Gio.ListModel
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable

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

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

foreign import ccall "gtk_string_list_get_type"
    c_gtk_string_list_get_type :: IO B.Types.GType

instance B.Types.TypedObject StringList where
    glibType :: IO GType
glibType = IO GType
c_gtk_string_list_get_type

instance B.Types.GObject StringList

-- | Type class for types which can be safely cast to `StringList`, for instance with `toStringList`.
class (SP.GObject o, O.IsDescendantOf StringList o) => IsStringList o
instance (SP.GObject o, O.IsDescendantOf StringList o) => IsStringList o

instance O.HasParentTypes StringList
type instance O.ParentTypes StringList = '[GObject.Object.Object, Gio.ListModel.ListModel, Gtk.Buildable.Buildable]

-- | Cast to `StringList`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toStringList :: (MIO.MonadIO m, IsStringList o) => o -> m StringList
toStringList :: forall (m :: * -> *) o.
(MonadIO m, IsStringList o) =>
o -> m StringList
toStringList = IO StringList -> m StringList
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO StringList -> m StringList)
-> (o -> IO StringList) -> o -> m StringList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr StringList -> StringList) -> o -> IO StringList
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr StringList -> StringList
StringList

-- | Convert 'StringList' 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 StringList) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_string_list_get_type
    gvalueSet_ :: Ptr GValue -> Maybe StringList -> IO ()
gvalueSet_ Ptr GValue
gv Maybe StringList
P.Nothing = Ptr GValue -> Ptr StringList -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr StringList
forall a. Ptr a
FP.nullPtr :: FP.Ptr StringList)
    gvalueSet_ Ptr GValue
gv (P.Just StringList
obj) = StringList -> (Ptr StringList -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr StringList
obj (Ptr GValue -> Ptr StringList -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe StringList)
gvalueGet_ Ptr GValue
gv = do
        Ptr StringList
ptr <- Ptr GValue -> IO (Ptr StringList)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr StringList)
        if Ptr StringList
ptr Ptr StringList -> Ptr StringList -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr StringList
forall a. Ptr a
FP.nullPtr
        then StringList -> Maybe StringList
forall a. a -> Maybe a
P.Just (StringList -> Maybe StringList)
-> IO StringList -> IO (Maybe StringList)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr StringList -> StringList)
-> Ptr StringList -> IO StringList
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr StringList -> StringList
StringList Ptr StringList
ptr
        else Maybe StringList -> IO (Maybe StringList)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe StringList
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveStringListMethod (t :: Symbol) (o :: *) :: * where
    ResolveStringListMethod "append" o = StringListAppendMethodInfo
    ResolveStringListMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveStringListMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveStringListMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveStringListMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveStringListMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveStringListMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveStringListMethod "itemsChanged" o = Gio.ListModel.ListModelItemsChangedMethodInfo
    ResolveStringListMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveStringListMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveStringListMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveStringListMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveStringListMethod "remove" o = StringListRemoveMethodInfo
    ResolveStringListMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveStringListMethod "splice" o = StringListSpliceMethodInfo
    ResolveStringListMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveStringListMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveStringListMethod "take" o = StringListTakeMethodInfo
    ResolveStringListMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveStringListMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveStringListMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveStringListMethod "getBuildableId" o = Gtk.Buildable.BuildableGetBuildableIdMethodInfo
    ResolveStringListMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveStringListMethod "getItem" o = Gio.ListModel.ListModelGetItemMethodInfo
    ResolveStringListMethod "getItemType" o = Gio.ListModel.ListModelGetItemTypeMethodInfo
    ResolveStringListMethod "getNItems" o = Gio.ListModel.ListModelGetNItemsMethodInfo
    ResolveStringListMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveStringListMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveStringListMethod "getString" o = StringListGetStringMethodInfo
    ResolveStringListMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveStringListMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveStringListMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveStringListMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

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

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList StringList = StringListSignalList
type StringListSignalList = ('[ '("itemsChanged", Gio.ListModel.ListModelItemsChangedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method StringList::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "strings"
--           , argType = TCArray True (-1) (-1) (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The strings to put in the model"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "StringList" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_string_list_new" gtk_string_list_new :: 
    Ptr CString ->                          -- strings : TCArray True (-1) (-1) (TBasicType TUTF8)
    IO (Ptr StringList)

-- | Creates a new @GtkStringList@ with the given /@strings@/.
stringListNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Maybe ([T.Text])
    -- ^ /@strings@/: The strings to put in the model
    -> m StringList
    -- ^ __Returns:__ a new @GtkStringList@
stringListNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Maybe [Text] -> m StringList
stringListNew Maybe [Text]
strings = IO StringList -> m StringList
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO StringList -> m StringList) -> IO StringList -> m StringList
forall a b. (a -> b) -> a -> b
$ do
    Ptr CString
maybeStrings <- case Maybe [Text]
strings of
        Maybe [Text]
Nothing -> Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
forall a. Ptr a
nullPtr
        Just [Text]
jStrings -> do
            Ptr CString
jStrings' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
jStrings
            Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
jStrings'
    Ptr StringList
result <- Ptr CString -> IO (Ptr StringList)
gtk_string_list_new Ptr CString
maybeStrings
    Text -> Ptr StringList -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stringListNew" Ptr StringList
result
    StringList
result' <- ((ManagedPtr StringList -> StringList)
-> Ptr StringList -> IO StringList
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr StringList -> StringList
StringList) Ptr StringList
result
    (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeStrings
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeStrings
    StringList -> IO StringList
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return StringList
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method StringList::append
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StringList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkStringList`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "string"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the string to insert"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_string_list_append" gtk_string_list_append :: 
    Ptr StringList ->                       -- self : TInterface (Name {namespace = "Gtk", name = "StringList"})
    CString ->                              -- string : TBasicType TUTF8
    IO ()

-- | Appends /@string@/ to /@self@/.
-- 
-- The /@string@/ will be copied. See
-- 'GI.Gtk.Objects.StringList.stringListTake' for a way to avoid that.
stringListAppend ::
    (B.CallStack.HasCallStack, MonadIO m, IsStringList a) =>
    a
    -- ^ /@self@/: a @GtkStringList@
    -> T.Text
    -- ^ /@string@/: the string to insert
    -> m ()
stringListAppend :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStringList a) =>
a -> Text -> m ()
stringListAppend a
self Text
string = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr StringList
self' <- a -> IO (Ptr StringList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
string' <- Text -> IO CString
textToCString Text
string
    Ptr StringList -> CString -> IO ()
gtk_string_list_append Ptr StringList
self' CString
string'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
string'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data StringListAppendMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsStringList a) => O.OverloadedMethod StringListAppendMethodInfo a signature where
    overloadedMethod = stringListAppend

instance O.OverloadedMethodInfo StringListAppendMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.StringList.stringListAppend",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-StringList.html#v:stringListAppend"
        })


#endif

-- method StringList::get_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StringList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkStringList`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "position"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the position to get the string for"
--                 , 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 "gtk_string_list_get_string" gtk_string_list_get_string :: 
    Ptr StringList ->                       -- self : TInterface (Name {namespace = "Gtk", name = "StringList"})
    Word32 ->                               -- position : TBasicType TUInt
    IO CString

-- | Gets the string that is at /@position@/ in /@self@/.
-- 
-- If /@self@/ does not contain /@position@/ items, 'P.Nothing' is returned.
-- 
-- This function returns the const char *. To get the
-- object wrapping it, use @/g_list_model_get_item()/@.
stringListGetString ::
    (B.CallStack.HasCallStack, MonadIO m, IsStringList a) =>
    a
    -- ^ /@self@/: a @GtkStringList@
    -> Word32
    -- ^ /@position@/: the position to get the string for
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the string at the given position
stringListGetString :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStringList a) =>
a -> Word32 -> m (Maybe Text)
stringListGetString a
self Word32
position = 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 StringList
self' <- a -> IO (Ptr StringList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr StringList -> Word32 -> IO CString
gtk_string_list_get_string Ptr StringList
self' Word32
position
    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'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    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 StringListGetStringMethodInfo
instance (signature ~ (Word32 -> m (Maybe T.Text)), MonadIO m, IsStringList a) => O.OverloadedMethod StringListGetStringMethodInfo a signature where
    overloadedMethod = stringListGetString

instance O.OverloadedMethodInfo StringListGetStringMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.StringList.stringListGetString",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-StringList.html#v:stringListGetString"
        })


#endif

-- method StringList::remove
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StringList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkStringList`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "position"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the position of the string that is to be removed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_string_list_remove" gtk_string_list_remove :: 
    Ptr StringList ->                       -- self : TInterface (Name {namespace = "Gtk", name = "StringList"})
    Word32 ->                               -- position : TBasicType TUInt
    IO ()

-- | Removes the string at /@position@/ from /@self@/.
-- 
-- /@position@/ must be smaller than the current
-- length of the list.
stringListRemove ::
    (B.CallStack.HasCallStack, MonadIO m, IsStringList a) =>
    a
    -- ^ /@self@/: a @GtkStringList@
    -> Word32
    -- ^ /@position@/: the position of the string that is to be removed
    -> m ()
stringListRemove :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStringList a) =>
a -> Word32 -> m ()
stringListRemove a
self Word32
position = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr StringList
self' <- a -> IO (Ptr StringList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr StringList -> Word32 -> IO ()
gtk_string_list_remove Ptr StringList
self' Word32
position
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data StringListRemoveMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsStringList a) => O.OverloadedMethod StringListRemoveMethodInfo a signature where
    overloadedMethod = stringListRemove

instance O.OverloadedMethodInfo StringListRemoveMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.StringList.stringListRemove",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-StringList.html#v:stringListRemove"
        })


#endif

-- method StringList::splice
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StringList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkStringList`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "position"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the position at which to make the change"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_removals"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of strings to remove"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "additions"
--           , argType = TCArray True (-1) (-1) (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The strings to add" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_string_list_splice" gtk_string_list_splice :: 
    Ptr StringList ->                       -- self : TInterface (Name {namespace = "Gtk", name = "StringList"})
    Word32 ->                               -- position : TBasicType TUInt
    Word32 ->                               -- n_removals : TBasicType TUInt
    Ptr CString ->                          -- additions : TCArray True (-1) (-1) (TBasicType TUTF8)
    IO ()

-- | Changes /@self@/ by removing /@nRemovals@/ strings and adding /@additions@/
-- to it.
-- 
-- This function is more efficient than 'GI.Gtk.Objects.StringList.stringListAppend'
-- and 'GI.Gtk.Objects.StringList.stringListRemove', because it only emits the
-- [itemsChanged](#g:signal:itemsChanged) signal once for the change.
-- 
-- This function copies the strings in /@additions@/.
-- 
-- The parameters /@position@/ and /@nRemovals@/ must be correct (ie:
-- /@position@/ + /@nRemovals@/ must be less than or equal to the length
-- of the list at the time this function is called).
stringListSplice ::
    (B.CallStack.HasCallStack, MonadIO m, IsStringList a) =>
    a
    -- ^ /@self@/: a @GtkStringList@
    -> Word32
    -- ^ /@position@/: the position at which to make the change
    -> Word32
    -- ^ /@nRemovals@/: the number of strings to remove
    -> Maybe ([T.Text])
    -- ^ /@additions@/: The strings to add
    -> m ()
stringListSplice :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStringList a) =>
a -> Word32 -> Word32 -> Maybe [Text] -> m ()
stringListSplice a
self Word32
position Word32
nRemovals Maybe [Text]
additions = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr StringList
self' <- a -> IO (Ptr StringList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr CString
maybeAdditions <- case Maybe [Text]
additions of
        Maybe [Text]
Nothing -> Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
forall a. Ptr a
nullPtr
        Just [Text]
jAdditions -> do
            Ptr CString
jAdditions' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
jAdditions
            Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
jAdditions'
    Ptr StringList -> Word32 -> Word32 -> Ptr CString -> IO ()
gtk_string_list_splice Ptr StringList
self' Word32
position Word32
nRemovals Ptr CString
maybeAdditions
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeAdditions
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybeAdditions
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data StringListSpliceMethodInfo
instance (signature ~ (Word32 -> Word32 -> Maybe ([T.Text]) -> m ()), MonadIO m, IsStringList a) => O.OverloadedMethod StringListSpliceMethodInfo a signature where
    overloadedMethod = stringListSplice

instance O.OverloadedMethodInfo StringListSpliceMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.StringList.stringListSplice",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-StringList.html#v:stringListSplice"
        })


#endif

-- method StringList::take
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StringList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkStringList`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "string"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the string to insert"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_string_list_take" gtk_string_list_take :: 
    Ptr StringList ->                       -- self : TInterface (Name {namespace = "Gtk", name = "StringList"})
    CString ->                              -- string : TBasicType TUTF8
    IO ()

-- | Adds /@string@/ to self at the end, and takes
-- ownership of it.
-- 
-- This variant of 'GI.Gtk.Objects.StringList.stringListAppend'
-- is convenient for formatting strings:
-- 
-- 
-- === /c code/
-- >gtk_string_list_take (self, g_strdup_print ("%d dollars", lots));
stringListTake ::
    (B.CallStack.HasCallStack, MonadIO m, IsStringList a) =>
    a
    -- ^ /@self@/: a @GtkStringList@
    -> T.Text
    -- ^ /@string@/: the string to insert
    -> m ()
stringListTake :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStringList a) =>
a -> Text -> m ()
stringListTake a
self Text
string = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr StringList
self' <- a -> IO (Ptr StringList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
string' <- Text -> IO CString
textToCString Text
string
    Ptr StringList -> CString -> IO ()
gtk_string_list_take Ptr StringList
self' CString
string'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data StringListTakeMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsStringList a) => O.OverloadedMethod StringListTakeMethodInfo a signature where
    overloadedMethod = stringListTake

instance O.OverloadedMethodInfo StringListTakeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.StringList.stringListTake",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-StringList.html#v:stringListTake"
        })


#endif