{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.Gtk.Objects.ListStore.ListStore' object is a list model for use with a t'GI.Gtk.Objects.TreeView.TreeView'
-- widget.  It implements the t'GI.Gtk.Interfaces.TreeModel.TreeModel' interface, and consequentialy,
-- can use all of the methods available there.  It also implements the
-- t'GI.Gtk.Interfaces.TreeSortable.TreeSortable' interface so it can be sorted by the view.
-- Finally, it also implements the tree
-- [drag and drop][gtk3-GtkTreeView-drag-and-drop]
-- interfaces.
-- 
-- The t'GI.Gtk.Objects.ListStore.ListStore' can accept most GObject types as a column type, though
-- it can’t accept all custom types.  Internally, it will keep a copy of
-- data passed in (such as a string or a boxed pointer).  Columns that
-- accept @/GObjects/@ are handled a little differently.  The
-- t'GI.Gtk.Objects.ListStore.ListStore' will keep a reference to the object instead of copying the
-- value.  As a result, if the object is modified, it is up to the
-- application writer to call 'GI.Gtk.Interfaces.TreeModel.treeModelRowChanged' to emit the
-- t'GI.Gtk.Interfaces.TreeModel.TreeModel'::@/row_changed/@ signal.  This most commonly affects lists with
-- @/GdkPixbufs/@ stored.
-- 
-- An example for creating a simple list store:
-- 
-- === /C code/
-- >
-- >enum {
-- >  COLUMN_STRING,
-- >  COLUMN_INT,
-- >  COLUMN_BOOLEAN,
-- >  N_COLUMNS
-- >};
-- >
-- >{
-- >  GtkListStore *list_store;
-- >  GtkTreePath *path;
-- >  GtkTreeIter iter;
-- >  gint i;
-- >
-- >  list_store = gtk_list_store_new (N_COLUMNS,
-- >                                   G_TYPE_STRING,
-- >                                   G_TYPE_INT,
-- >                                   G_TYPE_BOOLEAN);
-- >
-- >  for (i = 0; i < 10; i++)
-- >    {
-- >      gchar *some_data;
-- >
-- >      some_data = get_some_data (i);
-- >
-- >      // Add a new row to the model
-- >      gtk_list_store_append (list_store, &iter);
-- >      gtk_list_store_set (list_store, &iter,
-- >                          COLUMN_STRING, some_data,
-- >                          COLUMN_INT, i,
-- >                          COLUMN_BOOLEAN,  FALSE,
-- >                          -1);
-- >
-- >      // As the store will keep a copy of the string internally,
-- >      // we free some_data.
-- >      g_free (some_data);
-- >    }
-- >
-- >  // Modify a particular row
-- >  path = gtk_tree_path_new_from_string ("4");
-- >  gtk_tree_model_get_iter (GTK_TREE_MODEL (list_store),
-- >                           &iter,
-- >                           path);
-- >  gtk_tree_path_free (path);
-- >  gtk_list_store_set (list_store, &iter,
-- >                      COLUMN_BOOLEAN, TRUE,
-- >                      -1);
-- >}
-- 
-- 
-- = Performance Considerations
-- 
-- Internally, the t'GI.Gtk.Objects.ListStore.ListStore' was implemented with a linked list with
-- a tail pointer prior to GTK+ 2.6.  As a result, it was fast at data
-- insertion and deletion, and not fast at random data access.  The
-- t'GI.Gtk.Objects.ListStore.ListStore' sets the @/GTK_TREE_MODEL_ITERS_PERSIST/@ flag, which means
-- that @/GtkTreeIters/@ can be cached while the row exists.  Thus, if
-- access to a particular row is needed often and your code is expected to
-- run on older versions of GTK+, it is worth keeping the iter around.
-- 
-- = Atomic Operations
-- 
-- It is important to note that only the methods
-- @/gtk_list_store_insert_with_values()/@ and 'GI.Gtk.Objects.ListStore.listStoreInsertWithValuesv'
-- are atomic, in the sense that the row is being appended to the store and the
-- values filled in in a single operation with regard to t'GI.Gtk.Interfaces.TreeModel.TreeModel' signaling.
-- In contrast, using e.g. 'GI.Gtk.Objects.ListStore.listStoreAppend' and then @/gtk_list_store_set()/@
-- will first create a row, which triggers the [rowInserted]("GI.Gtk.Interfaces.TreeModel#signal:rowInserted") signal
-- on t'GI.Gtk.Objects.ListStore.ListStore'. The row, however, is still empty, and any signal handler
-- connecting to [rowInserted]("GI.Gtk.Interfaces.TreeModel#signal:rowInserted") on this particular store should be prepared
-- for the situation that the row might be empty. This is especially important
-- if you are wrapping the t'GI.Gtk.Objects.ListStore.ListStore' inside a t'GI.Gtk.Objects.TreeModelFilter.TreeModelFilter' and are
-- using a t'GI.Gtk.Callbacks.TreeModelFilterVisibleFunc'. Using any of the non-atomic operations
-- to append rows to the t'GI.Gtk.Objects.ListStore.ListStore' will cause the
-- t'GI.Gtk.Callbacks.TreeModelFilterVisibleFunc' to be visited with an empty row first; the
-- function must be prepared for that.
-- 
-- = GtkListStore as GtkBuildable
-- 
-- The GtkListStore implementation of the GtkBuildable interface allows
-- to specify the model columns with a \<columns> element that may contain
-- multiple \<column> elements, each specifying one model column. The “type”
-- attribute specifies the data type for the column.
-- 
-- Additionally, it is possible to specify content for the list store
-- in the UI definition, with the \<data> element. It can contain multiple
-- \<row> elements, each specifying to content for one row of the list model.
-- Inside a \<row>, the \<col> elements specify the content for individual cells.
-- 
-- Note that it is probably more common to define your models in the code,
-- and one might consider it a layering violation to specify the content of
-- a list store in a UI definition, data, not presentation, and common wisdom
-- is to separate the two, as far as possible.
-- 
-- An example of a UI Definition fragment for a list store:
-- 
-- === /C code/
-- >
-- ><object class="GtkListStore">
-- >  <columns>
-- >    <column type="gchararray"/>
-- >    <column type="gchararray"/>
-- >    <column type="gint"/>
-- >  </columns>
-- >  <data>
-- >    <row>
-- >      <col id="0">John</col>
-- >      <col id="1">Doe</col>
-- >      <col id="2">25</col>
-- >    </row>
-- >    <row>
-- >      <col id="0">Johan</col>
-- >      <col id="1">Dahlin</col>
-- >      <col id="2">50</col>
-- >    </row>
-- >  </data>
-- ></object>
-- 

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

module GI.Gtk.Objects.ListStore
    ( 

-- * Exported types
    ListStore(..)                           ,
    IsListStore                             ,
    toListStore                             ,
    noListStore                             ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveListStoreMethod                  ,
#endif


-- ** append #method:append#

#if defined(ENABLE_OVERLOADING)
    ListStoreAppendMethodInfo               ,
#endif
    listStoreAppend                         ,


-- ** clear #method:clear#

#if defined(ENABLE_OVERLOADING)
    ListStoreClearMethodInfo                ,
#endif
    listStoreClear                          ,


-- ** insert #method:insert#

#if defined(ENABLE_OVERLOADING)
    ListStoreInsertMethodInfo               ,
#endif
    listStoreInsert                         ,


-- ** insertAfter #method:insertAfter#

#if defined(ENABLE_OVERLOADING)
    ListStoreInsertAfterMethodInfo          ,
#endif
    listStoreInsertAfter                    ,


-- ** insertBefore #method:insertBefore#

#if defined(ENABLE_OVERLOADING)
    ListStoreInsertBeforeMethodInfo         ,
#endif
    listStoreInsertBefore                   ,


-- ** insertWithValuesv #method:insertWithValuesv#

#if defined(ENABLE_OVERLOADING)
    ListStoreInsertWithValuesvMethodInfo    ,
#endif
    listStoreInsertWithValuesv              ,


-- ** iterIsValid #method:iterIsValid#

#if defined(ENABLE_OVERLOADING)
    ListStoreIterIsValidMethodInfo          ,
#endif
    listStoreIterIsValid                    ,


-- ** moveAfter #method:moveAfter#

#if defined(ENABLE_OVERLOADING)
    ListStoreMoveAfterMethodInfo            ,
#endif
    listStoreMoveAfter                      ,


-- ** moveBefore #method:moveBefore#

#if defined(ENABLE_OVERLOADING)
    ListStoreMoveBeforeMethodInfo           ,
#endif
    listStoreMoveBefore                     ,


-- ** new #method:new#

    listStoreNew                            ,


-- ** prepend #method:prepend#

#if defined(ENABLE_OVERLOADING)
    ListStorePrependMethodInfo              ,
#endif
    listStorePrepend                        ,


-- ** remove #method:remove#

#if defined(ENABLE_OVERLOADING)
    ListStoreRemoveMethodInfo               ,
#endif
    listStoreRemove                         ,


-- ** reorder #method:reorder#

#if defined(ENABLE_OVERLOADING)
    ListStoreReorderMethodInfo              ,
#endif
    listStoreReorder                        ,


-- ** set #method:set#

#if defined(ENABLE_OVERLOADING)
    ListStoreSetMethodInfo                  ,
#endif
    listStoreSet                            ,


-- ** setColumnTypes #method:setColumnTypes#

#if defined(ENABLE_OVERLOADING)
    ListStoreSetColumnTypesMethodInfo       ,
#endif
    listStoreSetColumnTypes                 ,


-- ** setValue #method:setValue#

#if defined(ENABLE_OVERLOADING)
    ListStoreSetValueMethodInfo             ,
#endif
    listStoreSetValue                       ,


-- ** swap #method:swap#

#if defined(ENABLE_OVERLOADING)
    ListStoreSwapMethodInfo                 ,
#endif
    listStoreSwap                           ,




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified 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 GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.TreeDragDest as Gtk.TreeDragDest
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.TreeDragSource as Gtk.TreeDragSource
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.TreeModel as Gtk.TreeModel
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.TreeSortable as Gtk.TreeSortable
import {-# SOURCE #-} qualified GI.Gtk.Structs.TreeIter as Gtk.TreeIter

-- | Memory-managed wrapper type.
newtype ListStore = ListStore (ManagedPtr ListStore)
    deriving (ListStore -> ListStore -> Bool
(ListStore -> ListStore -> Bool)
-> (ListStore -> ListStore -> Bool) -> Eq ListStore
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListStore -> ListStore -> Bool
$c/= :: ListStore -> ListStore -> Bool
== :: ListStore -> ListStore -> Bool
$c== :: ListStore -> ListStore -> Bool
Eq)
foreign import ccall "gtk_list_store_get_type"
    c_gtk_list_store_get_type :: IO GType

instance GObject ListStore where
    gobjectType :: IO GType
gobjectType = IO GType
c_gtk_list_store_get_type
    

-- | Convert 'ListStore' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue ListStore where
    toGValue :: ListStore -> IO GValue
toGValue o :: ListStore
o = do
        GType
gtype <- IO GType
c_gtk_list_store_get_type
        ListStore -> (Ptr ListStore -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ListStore
o (GType
-> (GValue -> Ptr ListStore -> IO ()) -> Ptr ListStore -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr ListStore -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO ListStore
fromGValue gv :: GValue
gv = do
        Ptr ListStore
ptr <- GValue -> IO (Ptr ListStore)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr ListStore)
        (ManagedPtr ListStore -> ListStore)
-> Ptr ListStore -> IO ListStore
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr ListStore -> ListStore
ListStore Ptr ListStore
ptr
        
    

-- | Type class for types which can be safely cast to `ListStore`, for instance with `toListStore`.
class (GObject o, O.IsDescendantOf ListStore o) => IsListStore o
instance (GObject o, O.IsDescendantOf ListStore o) => IsListStore o

instance O.HasParentTypes ListStore
type instance O.ParentTypes ListStore = '[GObject.Object.Object, Gtk.Buildable.Buildable, Gtk.TreeDragDest.TreeDragDest, Gtk.TreeDragSource.TreeDragSource, Gtk.TreeModel.TreeModel, Gtk.TreeSortable.TreeSortable]

-- | Cast to `ListStore`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toListStore :: (MonadIO m, IsListStore o) => o -> m ListStore
toListStore :: o -> m ListStore
toListStore = IO ListStore -> m ListStore
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ListStore -> m ListStore)
-> (o -> IO ListStore) -> o -> m ListStore
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr ListStore -> ListStore) -> o -> IO ListStore
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr ListStore -> ListStore
ListStore

-- | A convenience alias for `Nothing` :: `Maybe` `ListStore`.
noListStore :: Maybe ListStore
noListStore :: Maybe ListStore
noListStore = Maybe ListStore
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveListStoreMethod (t :: Symbol) (o :: *) :: * where
    ResolveListStoreMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
    ResolveListStoreMethod "append" o = ListStoreAppendMethodInfo
    ResolveListStoreMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveListStoreMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveListStoreMethod "clear" o = ListStoreClearMethodInfo
    ResolveListStoreMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
    ResolveListStoreMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
    ResolveListStoreMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
    ResolveListStoreMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
    ResolveListStoreMethod "dragDataDelete" o = Gtk.TreeDragSource.TreeDragSourceDragDataDeleteMethodInfo
    ResolveListStoreMethod "dragDataGet" o = Gtk.TreeDragSource.TreeDragSourceDragDataGetMethodInfo
    ResolveListStoreMethod "dragDataReceived" o = Gtk.TreeDragDest.TreeDragDestDragDataReceivedMethodInfo
    ResolveListStoreMethod "filterNew" o = Gtk.TreeModel.TreeModelFilterNewMethodInfo
    ResolveListStoreMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveListStoreMethod "foreach" o = Gtk.TreeModel.TreeModelForeachMethodInfo
    ResolveListStoreMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveListStoreMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveListStoreMethod "hasDefaultSortFunc" o = Gtk.TreeSortable.TreeSortableHasDefaultSortFuncMethodInfo
    ResolveListStoreMethod "insert" o = ListStoreInsertMethodInfo
    ResolveListStoreMethod "insertAfter" o = ListStoreInsertAfterMethodInfo
    ResolveListStoreMethod "insertBefore" o = ListStoreInsertBeforeMethodInfo
    ResolveListStoreMethod "insertWithValuesv" o = ListStoreInsertWithValuesvMethodInfo
    ResolveListStoreMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveListStoreMethod "iterChildren" o = Gtk.TreeModel.TreeModelIterChildrenMethodInfo
    ResolveListStoreMethod "iterHasChild" o = Gtk.TreeModel.TreeModelIterHasChildMethodInfo
    ResolveListStoreMethod "iterIsValid" o = ListStoreIterIsValidMethodInfo
    ResolveListStoreMethod "iterNChildren" o = Gtk.TreeModel.TreeModelIterNChildrenMethodInfo
    ResolveListStoreMethod "iterNext" o = Gtk.TreeModel.TreeModelIterNextMethodInfo
    ResolveListStoreMethod "iterNthChild" o = Gtk.TreeModel.TreeModelIterNthChildMethodInfo
    ResolveListStoreMethod "iterParent" o = Gtk.TreeModel.TreeModelIterParentMethodInfo
    ResolveListStoreMethod "iterPrevious" o = Gtk.TreeModel.TreeModelIterPreviousMethodInfo
    ResolveListStoreMethod "moveAfter" o = ListStoreMoveAfterMethodInfo
    ResolveListStoreMethod "moveBefore" o = ListStoreMoveBeforeMethodInfo
    ResolveListStoreMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveListStoreMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveListStoreMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
    ResolveListStoreMethod "prepend" o = ListStorePrependMethodInfo
    ResolveListStoreMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveListStoreMethod "refNode" o = Gtk.TreeModel.TreeModelRefNodeMethodInfo
    ResolveListStoreMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveListStoreMethod "remove" o = ListStoreRemoveMethodInfo
    ResolveListStoreMethod "reorder" o = ListStoreReorderMethodInfo
    ResolveListStoreMethod "rowChanged" o = Gtk.TreeModel.TreeModelRowChangedMethodInfo
    ResolveListStoreMethod "rowDeleted" o = Gtk.TreeModel.TreeModelRowDeletedMethodInfo
    ResolveListStoreMethod "rowDraggable" o = Gtk.TreeDragSource.TreeDragSourceRowDraggableMethodInfo
    ResolveListStoreMethod "rowDropPossible" o = Gtk.TreeDragDest.TreeDragDestRowDropPossibleMethodInfo
    ResolveListStoreMethod "rowHasChildToggled" o = Gtk.TreeModel.TreeModelRowHasChildToggledMethodInfo
    ResolveListStoreMethod "rowInserted" o = Gtk.TreeModel.TreeModelRowInsertedMethodInfo
    ResolveListStoreMethod "rowsReordered" o = Gtk.TreeModel.TreeModelRowsReorderedMethodInfo
    ResolveListStoreMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveListStoreMethod "set" o = ListStoreSetMethodInfo
    ResolveListStoreMethod "sortColumnChanged" o = Gtk.TreeSortable.TreeSortableSortColumnChangedMethodInfo
    ResolveListStoreMethod "sortNewWithModel" o = Gtk.TreeModel.TreeModelSortNewWithModelMethodInfo
    ResolveListStoreMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveListStoreMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveListStoreMethod "swap" o = ListStoreSwapMethodInfo
    ResolveListStoreMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveListStoreMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveListStoreMethod "unrefNode" o = Gtk.TreeModel.TreeModelUnrefNodeMethodInfo
    ResolveListStoreMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveListStoreMethod "getColumnType" o = Gtk.TreeModel.TreeModelGetColumnTypeMethodInfo
    ResolveListStoreMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveListStoreMethod "getFlags" o = Gtk.TreeModel.TreeModelGetFlagsMethodInfo
    ResolveListStoreMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
    ResolveListStoreMethod "getIter" o = Gtk.TreeModel.TreeModelGetIterMethodInfo
    ResolveListStoreMethod "getIterFirst" o = Gtk.TreeModel.TreeModelGetIterFirstMethodInfo
    ResolveListStoreMethod "getIterFromString" o = Gtk.TreeModel.TreeModelGetIterFromStringMethodInfo
    ResolveListStoreMethod "getNColumns" o = Gtk.TreeModel.TreeModelGetNColumnsMethodInfo
    ResolveListStoreMethod "getName" o = Gtk.Buildable.BuildableGetNameMethodInfo
    ResolveListStoreMethod "getPath" o = Gtk.TreeModel.TreeModelGetPathMethodInfo
    ResolveListStoreMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveListStoreMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveListStoreMethod "getSortColumnId" o = Gtk.TreeSortable.TreeSortableGetSortColumnIdMethodInfo
    ResolveListStoreMethod "getStringFromIter" o = Gtk.TreeModel.TreeModelGetStringFromIterMethodInfo
    ResolveListStoreMethod "getValue" o = Gtk.TreeModel.TreeModelGetValueMethodInfo
    ResolveListStoreMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
    ResolveListStoreMethod "setColumnTypes" o = ListStoreSetColumnTypesMethodInfo
    ResolveListStoreMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveListStoreMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveListStoreMethod "setDefaultSortFunc" o = Gtk.TreeSortable.TreeSortableSetDefaultSortFuncMethodInfo
    ResolveListStoreMethod "setName" o = Gtk.Buildable.BuildableSetNameMethodInfo
    ResolveListStoreMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveListStoreMethod "setSortColumnId" o = Gtk.TreeSortable.TreeSortableSetSortColumnIdMethodInfo
    ResolveListStoreMethod "setSortFunc" o = Gtk.TreeSortable.TreeSortableSetSortFuncMethodInfo
    ResolveListStoreMethod "setValue" o = ListStoreSetValueMethodInfo
    ResolveListStoreMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveListStoreMethod t ListStore, O.MethodInfo info ListStore p) => OL.IsLabel t (ListStore -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

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

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ListStore = ListStoreSignalList
type ListStoreSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo), '("rowChanged", Gtk.TreeModel.TreeModelRowChangedSignalInfo), '("rowDeleted", Gtk.TreeModel.TreeModelRowDeletedSignalInfo), '("rowHasChildToggled", Gtk.TreeModel.TreeModelRowHasChildToggledSignalInfo), '("rowInserted", Gtk.TreeModel.TreeModelRowInsertedSignalInfo), '("sortColumnChanged", Gtk.TreeSortable.TreeSortableSortColumnChangedSignalInfo)] :: [(Symbol, *)])

#endif

-- method ListStore::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "n_columns"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of columns in the list store"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "types"
--           , argType = TCArray False (-1) 0 (TBasicType TGType)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "an array of #GType types for the columns, from first to last"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_columns"
--              , argType = TBasicType TInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "number of columns in the list store"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "ListStore" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_list_store_newv" gtk_list_store_newv :: 
    Int32 ->                                -- n_columns : TBasicType TInt
    Ptr CGType ->                           -- types : TCArray False (-1) 0 (TBasicType TGType)
    IO (Ptr ListStore)

-- | Non-vararg creation function.  Used primarily by language bindings.
listStoreNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [GType]
    -- ^ /@types@/: an array of t'GType' types for the columns, from first to last
    -> m ListStore
    -- ^ __Returns:__ a new t'GI.Gtk.Objects.ListStore.ListStore'
listStoreNew :: [GType] -> m ListStore
listStoreNew types :: [GType]
types = IO ListStore -> m ListStore
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ListStore -> m ListStore) -> IO ListStore -> m ListStore
forall a b. (a -> b) -> a -> b
$ do
    let nColumns :: Int32
nColumns = Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ [GType] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [GType]
types
    Ptr CGType
types' <- ((GType -> CGType) -> [GType] -> IO (Ptr CGType)
forall a b. Storable b => (a -> b) -> [a] -> IO (Ptr b)
packMapStorableArray GType -> CGType
gtypeToCGType) [GType]
types
    Ptr ListStore
result <- Int32 -> Ptr CGType -> IO (Ptr ListStore)
gtk_list_store_newv Int32
nColumns Ptr CGType
types'
    Text -> Ptr ListStore -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "listStoreNew" Ptr ListStore
result
    ListStore
result' <- ((ManagedPtr ListStore -> ListStore)
-> Ptr ListStore -> IO ListStore
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr ListStore -> ListStore
ListStore) Ptr ListStore
result
    Ptr CGType -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CGType
types'
    ListStore -> IO ListStore
forall (m :: * -> *) a. Monad m => a -> m a
return ListStore
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method ListStore::append
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list_store"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ListStore" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GtkListStore" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreeIter" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "An unset #GtkTreeIter to set to the appended row"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_list_store_append" gtk_list_store_append :: 
    Ptr ListStore ->                        -- list_store : TInterface (Name {namespace = "Gtk", name = "ListStore"})
    Ptr Gtk.TreeIter.TreeIter ->            -- iter : TInterface (Name {namespace = "Gtk", name = "TreeIter"})
    IO ()

-- | Appends a new row to /@listStore@/.  /@iter@/ will be changed to point to this new
-- row.  The row will be empty after this function is called.  To fill in
-- values, you need to call @/gtk_list_store_set()/@ or 'GI.Gtk.Objects.ListStore.listStoreSetValue'.
listStoreAppend ::
    (B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
    a
    -- ^ /@listStore@/: A t'GI.Gtk.Objects.ListStore.ListStore'
    -> m (Gtk.TreeIter.TreeIter)
listStoreAppend :: a -> m TreeIter
listStoreAppend listStore :: a
listStore = IO TreeIter -> m TreeIter
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TreeIter -> m TreeIter) -> IO TreeIter -> m TreeIter
forall a b. (a -> b) -> a -> b
$ do
    Ptr ListStore
listStore' <- a -> IO (Ptr ListStore)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
listStore
    Ptr TreeIter
iter <- Int -> IO (Ptr TreeIter)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 32 :: IO (Ptr Gtk.TreeIter.TreeIter)
    Ptr ListStore -> Ptr TreeIter -> IO ()
gtk_list_store_append Ptr ListStore
listStore' Ptr TreeIter
iter
    TreeIter
iter' <- ((ManagedPtr TreeIter -> TreeIter) -> Ptr TreeIter -> IO TreeIter
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TreeIter -> TreeIter
Gtk.TreeIter.TreeIter) Ptr TreeIter
iter
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
listStore
    TreeIter -> IO TreeIter
forall (m :: * -> *) a. Monad m => a -> m a
return TreeIter
iter'

#if defined(ENABLE_OVERLOADING)
data ListStoreAppendMethodInfo
instance (signature ~ (m (Gtk.TreeIter.TreeIter)), MonadIO m, IsListStore a) => O.MethodInfo ListStoreAppendMethodInfo a signature where
    overloadedMethod = listStoreAppend

#endif

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

foreign import ccall "gtk_list_store_clear" gtk_list_store_clear :: 
    Ptr ListStore ->                        -- list_store : TInterface (Name {namespace = "Gtk", name = "ListStore"})
    IO ()

-- | Removes all rows from the list store.
listStoreClear ::
    (B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
    a
    -- ^ /@listStore@/: a t'GI.Gtk.Objects.ListStore.ListStore'.
    -> m ()
listStoreClear :: a -> m ()
listStoreClear listStore :: a
listStore = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr ListStore
listStore' <- a -> IO (Ptr ListStore)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
listStore
    Ptr ListStore -> IO ()
gtk_list_store_clear Ptr ListStore
listStore'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
listStore
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ListStoreClearMethodInfo
instance (signature ~ (m ()), MonadIO m, IsListStore a) => O.MethodInfo ListStoreClearMethodInfo a signature where
    overloadedMethod = listStoreClear

#endif

-- method ListStore::insert
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list_store"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ListStore" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GtkListStore" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreeIter" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An unset #GtkTreeIter to set to the new row"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "position"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "position to insert the new row, or -1 for last"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_list_store_insert" gtk_list_store_insert :: 
    Ptr ListStore ->                        -- list_store : TInterface (Name {namespace = "Gtk", name = "ListStore"})
    Ptr Gtk.TreeIter.TreeIter ->            -- iter : TInterface (Name {namespace = "Gtk", name = "TreeIter"})
    Int32 ->                                -- position : TBasicType TInt
    IO ()

-- | Creates a new row at /@position@/.  /@iter@/ will be changed to point to this new
-- row.  If /@position@/ is -1 or is larger than the number of rows on the list,
-- then the new row will be appended to the list. The row will be empty after
-- this function is called.  To fill in values, you need to call
-- @/gtk_list_store_set()/@ or 'GI.Gtk.Objects.ListStore.listStoreSetValue'.
listStoreInsert ::
    (B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
    a
    -- ^ /@listStore@/: A t'GI.Gtk.Objects.ListStore.ListStore'
    -> Int32
    -- ^ /@position@/: position to insert the new row, or -1 for last
    -> m (Gtk.TreeIter.TreeIter)
listStoreInsert :: a -> Int32 -> m TreeIter
listStoreInsert listStore :: a
listStore position :: Int32
position = IO TreeIter -> m TreeIter
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TreeIter -> m TreeIter) -> IO TreeIter -> m TreeIter
forall a b. (a -> b) -> a -> b
$ do
    Ptr ListStore
listStore' <- a -> IO (Ptr ListStore)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
listStore
    Ptr TreeIter
iter <- Int -> IO (Ptr TreeIter)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 32 :: IO (Ptr Gtk.TreeIter.TreeIter)
    Ptr ListStore -> Ptr TreeIter -> Int32 -> IO ()
gtk_list_store_insert Ptr ListStore
listStore' Ptr TreeIter
iter Int32
position
    TreeIter
iter' <- ((ManagedPtr TreeIter -> TreeIter) -> Ptr TreeIter -> IO TreeIter
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TreeIter -> TreeIter
Gtk.TreeIter.TreeIter) Ptr TreeIter
iter
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
listStore
    TreeIter -> IO TreeIter
forall (m :: * -> *) a. Monad m => a -> m a
return TreeIter
iter'

#if defined(ENABLE_OVERLOADING)
data ListStoreInsertMethodInfo
instance (signature ~ (Int32 -> m (Gtk.TreeIter.TreeIter)), MonadIO m, IsListStore a) => O.MethodInfo ListStoreInsertMethodInfo a signature where
    overloadedMethod = listStoreInsert

#endif

-- method ListStore::insert_after
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list_store"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ListStore" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GtkListStore" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreeIter" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An unset #GtkTreeIter to set to the new row"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "sibling"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreeIter" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A valid #GtkTreeIter, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_list_store_insert_after" gtk_list_store_insert_after :: 
    Ptr ListStore ->                        -- list_store : TInterface (Name {namespace = "Gtk", name = "ListStore"})
    Ptr Gtk.TreeIter.TreeIter ->            -- iter : TInterface (Name {namespace = "Gtk", name = "TreeIter"})
    Ptr Gtk.TreeIter.TreeIter ->            -- sibling : TInterface (Name {namespace = "Gtk", name = "TreeIter"})
    IO ()

-- | Inserts a new row after /@sibling@/. If /@sibling@/ is 'P.Nothing', then the row will be
-- prepended to the beginning of the list. /@iter@/ will be changed to point to
-- this new row. The row will be empty after this function is called. To fill
-- in values, you need to call @/gtk_list_store_set()/@ or 'GI.Gtk.Objects.ListStore.listStoreSetValue'.
listStoreInsertAfter ::
    (B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
    a
    -- ^ /@listStore@/: A t'GI.Gtk.Objects.ListStore.ListStore'
    -> Maybe (Gtk.TreeIter.TreeIter)
    -- ^ /@sibling@/: A valid t'GI.Gtk.Structs.TreeIter.TreeIter', or 'P.Nothing'
    -> m (Gtk.TreeIter.TreeIter)
listStoreInsertAfter :: a -> Maybe TreeIter -> m TreeIter
listStoreInsertAfter listStore :: a
listStore sibling :: Maybe TreeIter
sibling = IO TreeIter -> m TreeIter
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TreeIter -> m TreeIter) -> IO TreeIter -> m TreeIter
forall a b. (a -> b) -> a -> b
$ do
    Ptr ListStore
listStore' <- a -> IO (Ptr ListStore)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
listStore
    Ptr TreeIter
iter <- Int -> IO (Ptr TreeIter)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 32 :: IO (Ptr Gtk.TreeIter.TreeIter)
    Ptr TreeIter
maybeSibling <- case Maybe TreeIter
sibling of
        Nothing -> Ptr TreeIter -> IO (Ptr TreeIter)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TreeIter
forall a. Ptr a
nullPtr
        Just jSibling :: TreeIter
jSibling -> do
            Ptr TreeIter
jSibling' <- TreeIter -> IO (Ptr TreeIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreeIter
jSibling
            Ptr TreeIter -> IO (Ptr TreeIter)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TreeIter
jSibling'
    Ptr ListStore -> Ptr TreeIter -> Ptr TreeIter -> IO ()
gtk_list_store_insert_after Ptr ListStore
listStore' Ptr TreeIter
iter Ptr TreeIter
maybeSibling
    TreeIter
iter' <- ((ManagedPtr TreeIter -> TreeIter) -> Ptr TreeIter -> IO TreeIter
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TreeIter -> TreeIter
Gtk.TreeIter.TreeIter) Ptr TreeIter
iter
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
listStore
    Maybe TreeIter -> (TreeIter -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe TreeIter
sibling TreeIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    TreeIter -> IO TreeIter
forall (m :: * -> *) a. Monad m => a -> m a
return TreeIter
iter'

#if defined(ENABLE_OVERLOADING)
data ListStoreInsertAfterMethodInfo
instance (signature ~ (Maybe (Gtk.TreeIter.TreeIter) -> m (Gtk.TreeIter.TreeIter)), MonadIO m, IsListStore a) => O.MethodInfo ListStoreInsertAfterMethodInfo a signature where
    overloadedMethod = listStoreInsertAfter

#endif

-- method ListStore::insert_before
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list_store"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ListStore" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GtkListStore" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreeIter" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An unset #GtkTreeIter to set to the new row"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "sibling"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreeIter" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A valid #GtkTreeIter, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_list_store_insert_before" gtk_list_store_insert_before :: 
    Ptr ListStore ->                        -- list_store : TInterface (Name {namespace = "Gtk", name = "ListStore"})
    Ptr Gtk.TreeIter.TreeIter ->            -- iter : TInterface (Name {namespace = "Gtk", name = "TreeIter"})
    Ptr Gtk.TreeIter.TreeIter ->            -- sibling : TInterface (Name {namespace = "Gtk", name = "TreeIter"})
    IO ()

-- | Inserts a new row before /@sibling@/. If /@sibling@/ is 'P.Nothing', then the row will
-- be appended to the end of the list. /@iter@/ will be changed to point to this
-- new row. The row will be empty after this function is called. To fill in
-- values, you need to call @/gtk_list_store_set()/@ or 'GI.Gtk.Objects.ListStore.listStoreSetValue'.
listStoreInsertBefore ::
    (B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
    a
    -- ^ /@listStore@/: A t'GI.Gtk.Objects.ListStore.ListStore'
    -> Maybe (Gtk.TreeIter.TreeIter)
    -- ^ /@sibling@/: A valid t'GI.Gtk.Structs.TreeIter.TreeIter', or 'P.Nothing'
    -> m (Gtk.TreeIter.TreeIter)
listStoreInsertBefore :: a -> Maybe TreeIter -> m TreeIter
listStoreInsertBefore listStore :: a
listStore sibling :: Maybe TreeIter
sibling = IO TreeIter -> m TreeIter
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TreeIter -> m TreeIter) -> IO TreeIter -> m TreeIter
forall a b. (a -> b) -> a -> b
$ do
    Ptr ListStore
listStore' <- a -> IO (Ptr ListStore)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
listStore
    Ptr TreeIter
iter <- Int -> IO (Ptr TreeIter)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 32 :: IO (Ptr Gtk.TreeIter.TreeIter)
    Ptr TreeIter
maybeSibling <- case Maybe TreeIter
sibling of
        Nothing -> Ptr TreeIter -> IO (Ptr TreeIter)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TreeIter
forall a. Ptr a
nullPtr
        Just jSibling :: TreeIter
jSibling -> do
            Ptr TreeIter
jSibling' <- TreeIter -> IO (Ptr TreeIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreeIter
jSibling
            Ptr TreeIter -> IO (Ptr TreeIter)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TreeIter
jSibling'
    Ptr ListStore -> Ptr TreeIter -> Ptr TreeIter -> IO ()
gtk_list_store_insert_before Ptr ListStore
listStore' Ptr TreeIter
iter Ptr TreeIter
maybeSibling
    TreeIter
iter' <- ((ManagedPtr TreeIter -> TreeIter) -> Ptr TreeIter -> IO TreeIter
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TreeIter -> TreeIter
Gtk.TreeIter.TreeIter) Ptr TreeIter
iter
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
listStore
    Maybe TreeIter -> (TreeIter -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe TreeIter
sibling TreeIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    TreeIter -> IO TreeIter
forall (m :: * -> *) a. Monad m => a -> m a
return TreeIter
iter'

#if defined(ENABLE_OVERLOADING)
data ListStoreInsertBeforeMethodInfo
instance (signature ~ (Maybe (Gtk.TreeIter.TreeIter) -> m (Gtk.TreeIter.TreeIter)), MonadIO m, IsListStore a) => O.MethodInfo ListStoreInsertBeforeMethodInfo a signature where
    overloadedMethod = listStoreInsertBefore

#endif

-- method ListStore::insert_with_valuesv
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list_store"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ListStore" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GtkListStore" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreeIter" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "An unset #GtkTreeIter to set to the new row, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "position"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "position to insert the new row, or -1 for last"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "columns"
--           , argType = TCArray False (-1) 5 (TBasicType TInt)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an array of column numbers"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "values"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 5
--                 (TInterface Name { namespace = "GObject" , name = "Value" })
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an array of GValues"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_values"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the length of the @columns and @values arrays"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_values"
--              , argType = TBasicType TInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the length of the @columns and @values arrays"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          , Arg
--              { argCName = "n_values"
--              , argType = TBasicType TInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the length of the @columns and @values arrays"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_list_store_insert_with_valuesv" gtk_list_store_insert_with_valuesv :: 
    Ptr ListStore ->                        -- list_store : TInterface (Name {namespace = "Gtk", name = "ListStore"})
    Ptr Gtk.TreeIter.TreeIter ->            -- iter : TInterface (Name {namespace = "Gtk", name = "TreeIter"})
    Int32 ->                                -- position : TBasicType TInt
    Ptr Int32 ->                            -- columns : TCArray False (-1) 5 (TBasicType TInt)
    Ptr GValue ->                           -- values : TCArray False (-1) 5 (TInterface (Name {namespace = "GObject", name = "Value"}))
    Int32 ->                                -- n_values : TBasicType TInt
    IO ()

-- | A variant of @/gtk_list_store_insert_with_values()/@ which
-- takes the columns and values as two arrays, instead of
-- varargs. This function is mainly intended for
-- language-bindings.
-- 
-- /Since: 2.6/
listStoreInsertWithValuesv ::
    (B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
    a
    -- ^ /@listStore@/: A t'GI.Gtk.Objects.ListStore.ListStore'
    -> Int32
    -- ^ /@position@/: position to insert the new row, or -1 for last
    -> [Int32]
    -- ^ /@columns@/: an array of column numbers
    -> [GValue]
    -- ^ /@values@/: an array of GValues
    -> m (Gtk.TreeIter.TreeIter)
listStoreInsertWithValuesv :: a -> Int32 -> [Int32] -> [GValue] -> m TreeIter
listStoreInsertWithValuesv listStore :: a
listStore position :: Int32
position columns :: [Int32]
columns values :: [GValue]
values = IO TreeIter -> m TreeIter
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TreeIter -> m TreeIter) -> IO TreeIter -> m TreeIter
forall a b. (a -> b) -> a -> b
$ do
    let nValues :: Int32
nValues = Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ [GValue] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [GValue]
values
    let columns_expected_length_ :: Int32
columns_expected_length_ = Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ [Int32] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int32]
columns
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int32
columns_expected_length_ Int32 -> Int32 -> Bool
forall a. Eq a => a -> a -> Bool
/= Int32
nValues) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
        [Char] -> IO ()
forall a. HasCallStack => [Char] -> a
error "Gtk.listStoreInsertWithValuesv : length of 'columns' does not agree with that of 'values'."
    Ptr ListStore
listStore' <- a -> IO (Ptr ListStore)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
listStore
    Ptr TreeIter
iter <- Int -> IO (Ptr TreeIter)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 32 :: IO (Ptr Gtk.TreeIter.TreeIter)
    Ptr Int32
columns' <- [Int32] -> IO (Ptr Int32)
forall a. Storable a => [a] -> IO (Ptr a)
packStorableArray [Int32]
columns
    [Ptr GValue]
values' <- (GValue -> IO (Ptr GValue)) -> [GValue] -> IO [Ptr GValue]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [GValue]
values
    Ptr GValue
values'' <- Int -> [Ptr GValue] -> IO (Ptr GValue)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray 24 [Ptr GValue]
values'
    Ptr ListStore
-> Ptr TreeIter
-> Int32
-> Ptr Int32
-> Ptr GValue
-> Int32
-> IO ()
gtk_list_store_insert_with_valuesv Ptr ListStore
listStore' Ptr TreeIter
iter Int32
position Ptr Int32
columns' Ptr GValue
values'' Int32
nValues
    TreeIter
iter' <- ((ManagedPtr TreeIter -> TreeIter) -> Ptr TreeIter -> IO TreeIter
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TreeIter -> TreeIter
Gtk.TreeIter.TreeIter) Ptr TreeIter
iter
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
listStore
    (GValue -> IO ()) -> [GValue] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [GValue]
values
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
columns'
    Ptr GValue -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr GValue
values''
    TreeIter -> IO TreeIter
forall (m :: * -> *) a. Monad m => a -> m a
return TreeIter
iter'

#if defined(ENABLE_OVERLOADING)
data ListStoreInsertWithValuesvMethodInfo
instance (signature ~ (Int32 -> [Int32] -> [GValue] -> m (Gtk.TreeIter.TreeIter)), MonadIO m, IsListStore a) => O.MethodInfo ListStoreInsertWithValuesvMethodInfo a signature where
    overloadedMethod = listStoreInsertWithValuesv

#endif

-- method ListStore::iter_is_valid
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list_store"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ListStore" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GtkListStore." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreeIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GtkTreeIter." , 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 "gtk_list_store_iter_is_valid" gtk_list_store_iter_is_valid :: 
    Ptr ListStore ->                        -- list_store : TInterface (Name {namespace = "Gtk", name = "ListStore"})
    Ptr Gtk.TreeIter.TreeIter ->            -- iter : TInterface (Name {namespace = "Gtk", name = "TreeIter"})
    IO CInt

-- | > This function is slow. Only use it for debugging and\/or testing
-- > purposes.
-- 
-- Checks if the given iter is a valid iter for this t'GI.Gtk.Objects.ListStore.ListStore'.
-- 
-- /Since: 2.2/
listStoreIterIsValid ::
    (B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
    a
    -- ^ /@listStore@/: A t'GI.Gtk.Objects.ListStore.ListStore'.
    -> Gtk.TreeIter.TreeIter
    -- ^ /@iter@/: A t'GI.Gtk.Structs.TreeIter.TreeIter'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the iter is valid, 'P.False' if the iter is invalid.
listStoreIterIsValid :: a -> TreeIter -> m Bool
listStoreIterIsValid listStore :: a
listStore iter :: TreeIter
iter = IO Bool -> m Bool
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 ListStore
listStore' <- a -> IO (Ptr ListStore)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
listStore
    Ptr TreeIter
iter' <- TreeIter -> IO (Ptr TreeIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreeIter
iter
    CInt
result <- Ptr ListStore -> Ptr TreeIter -> IO CInt
gtk_list_store_iter_is_valid Ptr ListStore
listStore' Ptr TreeIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
listStore
    TreeIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreeIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ListStoreIterIsValidMethodInfo
instance (signature ~ (Gtk.TreeIter.TreeIter -> m Bool), MonadIO m, IsListStore a) => O.MethodInfo ListStoreIterIsValidMethodInfo a signature where
    overloadedMethod = listStoreIterIsValid

#endif

-- method ListStore::move_after
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "store"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ListStore" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GtkListStore." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreeIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GtkTreeIter." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "position"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreeIter" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GtkTreeIter or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_list_store_move_after" gtk_list_store_move_after :: 
    Ptr ListStore ->                        -- store : TInterface (Name {namespace = "Gtk", name = "ListStore"})
    Ptr Gtk.TreeIter.TreeIter ->            -- iter : TInterface (Name {namespace = "Gtk", name = "TreeIter"})
    Ptr Gtk.TreeIter.TreeIter ->            -- position : TInterface (Name {namespace = "Gtk", name = "TreeIter"})
    IO ()

-- | Moves /@iter@/ in /@store@/ to the position after /@position@/. Note that this
-- function only works with unsorted stores. If /@position@/ is 'P.Nothing', /@iter@/
-- will be moved to the start of the list.
-- 
-- /Since: 2.2/
listStoreMoveAfter ::
    (B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
    a
    -- ^ /@store@/: A t'GI.Gtk.Objects.ListStore.ListStore'.
    -> Gtk.TreeIter.TreeIter
    -- ^ /@iter@/: A t'GI.Gtk.Structs.TreeIter.TreeIter'.
    -> Maybe (Gtk.TreeIter.TreeIter)
    -- ^ /@position@/: A t'GI.Gtk.Structs.TreeIter.TreeIter' or 'P.Nothing'.
    -> m ()
listStoreMoveAfter :: a -> TreeIter -> Maybe TreeIter -> m ()
listStoreMoveAfter store :: a
store iter :: TreeIter
iter position :: Maybe TreeIter
position = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr ListStore
store' <- a -> IO (Ptr ListStore)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
store
    Ptr TreeIter
iter' <- TreeIter -> IO (Ptr TreeIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreeIter
iter
    Ptr TreeIter
maybePosition <- case Maybe TreeIter
position of
        Nothing -> Ptr TreeIter -> IO (Ptr TreeIter)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TreeIter
forall a. Ptr a
nullPtr
        Just jPosition :: TreeIter
jPosition -> do
            Ptr TreeIter
jPosition' <- TreeIter -> IO (Ptr TreeIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreeIter
jPosition
            Ptr TreeIter -> IO (Ptr TreeIter)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TreeIter
jPosition'
    Ptr ListStore -> Ptr TreeIter -> Ptr TreeIter -> IO ()
gtk_list_store_move_after Ptr ListStore
store' Ptr TreeIter
iter' Ptr TreeIter
maybePosition
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
store
    TreeIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreeIter
iter
    Maybe TreeIter -> (TreeIter -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe TreeIter
position TreeIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ListStoreMoveAfterMethodInfo
instance (signature ~ (Gtk.TreeIter.TreeIter -> Maybe (Gtk.TreeIter.TreeIter) -> m ()), MonadIO m, IsListStore a) => O.MethodInfo ListStoreMoveAfterMethodInfo a signature where
    overloadedMethod = listStoreMoveAfter

#endif

-- method ListStore::move_before
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "store"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ListStore" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GtkListStore." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreeIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GtkTreeIter." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "position"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreeIter" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GtkTreeIter, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_list_store_move_before" gtk_list_store_move_before :: 
    Ptr ListStore ->                        -- store : TInterface (Name {namespace = "Gtk", name = "ListStore"})
    Ptr Gtk.TreeIter.TreeIter ->            -- iter : TInterface (Name {namespace = "Gtk", name = "TreeIter"})
    Ptr Gtk.TreeIter.TreeIter ->            -- position : TInterface (Name {namespace = "Gtk", name = "TreeIter"})
    IO ()

-- | Moves /@iter@/ in /@store@/ to the position before /@position@/. Note that this
-- function only works with unsorted stores. If /@position@/ is 'P.Nothing', /@iter@/
-- will be moved to the end of the list.
-- 
-- /Since: 2.2/
listStoreMoveBefore ::
    (B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
    a
    -- ^ /@store@/: A t'GI.Gtk.Objects.ListStore.ListStore'.
    -> Gtk.TreeIter.TreeIter
    -- ^ /@iter@/: A t'GI.Gtk.Structs.TreeIter.TreeIter'.
    -> Maybe (Gtk.TreeIter.TreeIter)
    -- ^ /@position@/: A t'GI.Gtk.Structs.TreeIter.TreeIter', or 'P.Nothing'.
    -> m ()
listStoreMoveBefore :: a -> TreeIter -> Maybe TreeIter -> m ()
listStoreMoveBefore store :: a
store iter :: TreeIter
iter position :: Maybe TreeIter
position = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr ListStore
store' <- a -> IO (Ptr ListStore)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
store
    Ptr TreeIter
iter' <- TreeIter -> IO (Ptr TreeIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreeIter
iter
    Ptr TreeIter
maybePosition <- case Maybe TreeIter
position of
        Nothing -> Ptr TreeIter -> IO (Ptr TreeIter)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TreeIter
forall a. Ptr a
nullPtr
        Just jPosition :: TreeIter
jPosition -> do
            Ptr TreeIter
jPosition' <- TreeIter -> IO (Ptr TreeIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreeIter
jPosition
            Ptr TreeIter -> IO (Ptr TreeIter)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TreeIter
jPosition'
    Ptr ListStore -> Ptr TreeIter -> Ptr TreeIter -> IO ()
gtk_list_store_move_before Ptr ListStore
store' Ptr TreeIter
iter' Ptr TreeIter
maybePosition
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
store
    TreeIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreeIter
iter
    Maybe TreeIter -> (TreeIter -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe TreeIter
position TreeIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ListStoreMoveBeforeMethodInfo
instance (signature ~ (Gtk.TreeIter.TreeIter -> Maybe (Gtk.TreeIter.TreeIter) -> m ()), MonadIO m, IsListStore a) => O.MethodInfo ListStoreMoveBeforeMethodInfo a signature where
    overloadedMethod = listStoreMoveBefore

#endif

-- method ListStore::prepend
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list_store"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ListStore" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GtkListStore" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreeIter" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "An unset #GtkTreeIter to set to the prepend row"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_list_store_prepend" gtk_list_store_prepend :: 
    Ptr ListStore ->                        -- list_store : TInterface (Name {namespace = "Gtk", name = "ListStore"})
    Ptr Gtk.TreeIter.TreeIter ->            -- iter : TInterface (Name {namespace = "Gtk", name = "TreeIter"})
    IO ()

-- | Prepends a new row to /@listStore@/. /@iter@/ will be changed to point to this new
-- row. The row will be empty after this function is called. To fill in
-- values, you need to call @/gtk_list_store_set()/@ or 'GI.Gtk.Objects.ListStore.listStoreSetValue'.
listStorePrepend ::
    (B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
    a
    -- ^ /@listStore@/: A t'GI.Gtk.Objects.ListStore.ListStore'
    -> m (Gtk.TreeIter.TreeIter)
listStorePrepend :: a -> m TreeIter
listStorePrepend listStore :: a
listStore = IO TreeIter -> m TreeIter
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TreeIter -> m TreeIter) -> IO TreeIter -> m TreeIter
forall a b. (a -> b) -> a -> b
$ do
    Ptr ListStore
listStore' <- a -> IO (Ptr ListStore)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
listStore
    Ptr TreeIter
iter <- Int -> IO (Ptr TreeIter)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 32 :: IO (Ptr Gtk.TreeIter.TreeIter)
    Ptr ListStore -> Ptr TreeIter -> IO ()
gtk_list_store_prepend Ptr ListStore
listStore' Ptr TreeIter
iter
    TreeIter
iter' <- ((ManagedPtr TreeIter -> TreeIter) -> Ptr TreeIter -> IO TreeIter
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TreeIter -> TreeIter
Gtk.TreeIter.TreeIter) Ptr TreeIter
iter
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
listStore
    TreeIter -> IO TreeIter
forall (m :: * -> *) a. Monad m => a -> m a
return TreeIter
iter'

#if defined(ENABLE_OVERLOADING)
data ListStorePrependMethodInfo
instance (signature ~ (m (Gtk.TreeIter.TreeIter)), MonadIO m, IsListStore a) => O.MethodInfo ListStorePrependMethodInfo a signature where
    overloadedMethod = listStorePrepend

#endif

-- method ListStore::remove
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list_store"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ListStore" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GtkListStore" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreeIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A valid #GtkTreeIter"
--                 , 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 "gtk_list_store_remove" gtk_list_store_remove :: 
    Ptr ListStore ->                        -- list_store : TInterface (Name {namespace = "Gtk", name = "ListStore"})
    Ptr Gtk.TreeIter.TreeIter ->            -- iter : TInterface (Name {namespace = "Gtk", name = "TreeIter"})
    IO CInt

-- | Removes the given row from the list store.  After being removed,
-- /@iter@/ is set to be the next valid row, or invalidated if it pointed
-- to the last row in /@listStore@/.
listStoreRemove ::
    (B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
    a
    -- ^ /@listStore@/: A t'GI.Gtk.Objects.ListStore.ListStore'
    -> Gtk.TreeIter.TreeIter
    -- ^ /@iter@/: A valid t'GI.Gtk.Structs.TreeIter.TreeIter'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@iter@/ is valid, 'P.False' if not.
listStoreRemove :: a -> TreeIter -> m Bool
listStoreRemove listStore :: a
listStore iter :: TreeIter
iter = IO Bool -> m Bool
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 ListStore
listStore' <- a -> IO (Ptr ListStore)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
listStore
    Ptr TreeIter
iter' <- TreeIter -> IO (Ptr TreeIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreeIter
iter
    CInt
result <- Ptr ListStore -> Ptr TreeIter -> IO CInt
gtk_list_store_remove Ptr ListStore
listStore' Ptr TreeIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
listStore
    TreeIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreeIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ListStoreRemoveMethodInfo
instance (signature ~ (Gtk.TreeIter.TreeIter -> m Bool), MonadIO m, IsListStore a) => O.MethodInfo ListStoreRemoveMethodInfo a signature where
    overloadedMethod = listStoreRemove

#endif

-- method ListStore::reorder
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "store"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ListStore" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GtkListStore." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "new_order"
--           , argType = TCArray True (-1) (-1) (TBasicType TInt)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "an array of integers mapping the new\n     position of each child to its old position before the re-ordering,\n     i.e. @new_order`[newpos] = oldpos`. It must have\n     exactly as many items as the list store\8217s length."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_list_store_reorder" gtk_list_store_reorder :: 
    Ptr ListStore ->                        -- store : TInterface (Name {namespace = "Gtk", name = "ListStore"})
    Ptr Int32 ->                            -- new_order : TCArray True (-1) (-1) (TBasicType TInt)
    IO ()

-- | Reorders /@store@/ to follow the order indicated by /@newOrder@/. Note that
-- this function only works with unsorted stores.
-- 
-- /Since: 2.2/
listStoreReorder ::
    (B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
    a
    -- ^ /@store@/: A t'GI.Gtk.Objects.ListStore.ListStore'.
    -> [Int32]
    -- ^ /@newOrder@/: an array of integers mapping the new
    --      position of each child to its old position before the re-ordering,
    --      i.e. /@newOrder@/@[newpos] = oldpos@. It must have
    --      exactly as many items as the list store’s length.
    -> m ()
listStoreReorder :: a -> [Int32] -> m ()
listStoreReorder store :: a
store newOrder :: [Int32]
newOrder = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr ListStore
store' <- a -> IO (Ptr ListStore)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
store
    Ptr Int32
newOrder' <- [Int32] -> IO (Ptr Int32)
forall a. (Num a, Storable a) => [a] -> IO (Ptr a)
packZeroTerminatedStorableArray [Int32]
newOrder
    Ptr ListStore -> Ptr Int32 -> IO ()
gtk_list_store_reorder Ptr ListStore
store' Ptr Int32
newOrder'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
store
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
newOrder'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ListStoreReorderMethodInfo
instance (signature ~ ([Int32] -> m ()), MonadIO m, IsListStore a) => O.MethodInfo ListStoreReorderMethodInfo a signature where
    overloadedMethod = listStoreReorder

#endif

-- method ListStore::set_column_types
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list_store"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ListStore" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GtkListStore" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_columns"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Number of columns for the list store"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "types"
--           , argType = TCArray False (-1) 1 (TBasicType TGType)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An array length n of #GTypes"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_columns"
--              , argType = TBasicType TInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "Number of columns for the list store"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_list_store_set_column_types" gtk_list_store_set_column_types :: 
    Ptr ListStore ->                        -- list_store : TInterface (Name {namespace = "Gtk", name = "ListStore"})
    Int32 ->                                -- n_columns : TBasicType TInt
    Ptr CGType ->                           -- types : TCArray False (-1) 1 (TBasicType TGType)
    IO ()

-- | This function is meant primarily for @/GObjects/@ that inherit from t'GI.Gtk.Objects.ListStore.ListStore',
-- and should only be used when constructing a new t'GI.Gtk.Objects.ListStore.ListStore'.  It will not
-- function after a row has been added, or a method on the t'GI.Gtk.Interfaces.TreeModel.TreeModel'
-- interface is called.
listStoreSetColumnTypes ::
    (B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
    a
    -- ^ /@listStore@/: A t'GI.Gtk.Objects.ListStore.ListStore'
    -> [GType]
    -- ^ /@types@/: An array length n of @/GTypes/@
    -> m ()
listStoreSetColumnTypes :: a -> [GType] -> m ()
listStoreSetColumnTypes listStore :: a
listStore types :: [GType]
types = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    let nColumns :: Int32
nColumns = Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ [GType] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [GType]
types
    Ptr ListStore
listStore' <- a -> IO (Ptr ListStore)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
listStore
    Ptr CGType
types' <- ((GType -> CGType) -> [GType] -> IO (Ptr CGType)
forall a b. Storable b => (a -> b) -> [a] -> IO (Ptr b)
packMapStorableArray GType -> CGType
gtypeToCGType) [GType]
types
    Ptr ListStore -> Int32 -> Ptr CGType -> IO ()
gtk_list_store_set_column_types Ptr ListStore
listStore' Int32
nColumns Ptr CGType
types'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
listStore
    Ptr CGType -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CGType
types'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ListStoreSetColumnTypesMethodInfo
instance (signature ~ ([GType] -> m ()), MonadIO m, IsListStore a) => O.MethodInfo ListStoreSetColumnTypesMethodInfo a signature where
    overloadedMethod = listStoreSetColumnTypes

#endif

-- method ListStore::set_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list_store"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ListStore" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GtkListStore" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreeIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "A valid #GtkTreeIter for the row being modified"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "column"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "column number to modify"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Value" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "new value for the cell"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_list_store_set_value" gtk_list_store_set_value :: 
    Ptr ListStore ->                        -- list_store : TInterface (Name {namespace = "Gtk", name = "ListStore"})
    Ptr Gtk.TreeIter.TreeIter ->            -- iter : TInterface (Name {namespace = "Gtk", name = "TreeIter"})
    Int32 ->                                -- column : TBasicType TInt
    Ptr GValue ->                           -- value : TInterface (Name {namespace = "GObject", name = "Value"})
    IO ()

-- | Sets the data in the cell specified by /@iter@/ and /@column@/.
-- The type of /@value@/ must be convertible to the type of the
-- column.
listStoreSetValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
    a
    -- ^ /@listStore@/: A t'GI.Gtk.Objects.ListStore.ListStore'
    -> Gtk.TreeIter.TreeIter
    -- ^ /@iter@/: A valid t'GI.Gtk.Structs.TreeIter.TreeIter' for the row being modified
    -> Int32
    -- ^ /@column@/: column number to modify
    -> GValue
    -- ^ /@value@/: new value for the cell
    -> m ()
listStoreSetValue :: a -> TreeIter -> Int32 -> GValue -> m ()
listStoreSetValue listStore :: a
listStore iter :: TreeIter
iter column :: Int32
column value :: GValue
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr ListStore
listStore' <- a -> IO (Ptr ListStore)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
listStore
    Ptr TreeIter
iter' <- TreeIter -> IO (Ptr TreeIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreeIter
iter
    Ptr GValue
value' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
value
    Ptr ListStore -> Ptr TreeIter -> Int32 -> Ptr GValue -> IO ()
gtk_list_store_set_value Ptr ListStore
listStore' Ptr TreeIter
iter' Int32
column Ptr GValue
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
listStore
    TreeIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreeIter
iter
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
value
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ListStoreSetValueMethodInfo
instance (signature ~ (Gtk.TreeIter.TreeIter -> Int32 -> GValue -> m ()), MonadIO m, IsListStore a) => O.MethodInfo ListStoreSetValueMethodInfo a signature where
    overloadedMethod = listStoreSetValue

#endif

-- method ListStore::set
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list_store"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ListStore" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GtkListStore" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreeIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "A valid #GtkTreeIter for the row being modified"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "columns"
--           , argType = TCArray False (-1) 4 (TBasicType TInt)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an array of column numbers"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "values"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 4
--                 (TInterface Name { namespace = "GObject" , name = "Value" })
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an array of GValues"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_values"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the length of the @columns and @values arrays"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_values"
--              , argType = TBasicType TInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the length of the @columns and @values arrays"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          , Arg
--              { argCName = "n_values"
--              , argType = TBasicType TInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the length of the @columns and @values arrays"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_list_store_set_valuesv" gtk_list_store_set_valuesv :: 
    Ptr ListStore ->                        -- list_store : TInterface (Name {namespace = "Gtk", name = "ListStore"})
    Ptr Gtk.TreeIter.TreeIter ->            -- iter : TInterface (Name {namespace = "Gtk", name = "TreeIter"})
    Ptr Int32 ->                            -- columns : TCArray False (-1) 4 (TBasicType TInt)
    Ptr GValue ->                           -- values : TCArray False (-1) 4 (TInterface (Name {namespace = "GObject", name = "Value"}))
    Int32 ->                                -- n_values : TBasicType TInt
    IO ()

-- | A variant of @/gtk_list_store_set_valist()/@ which
-- takes the columns and values as two arrays, instead of
-- varargs. This function is mainly intended for
-- language-bindings and in case the number of columns to
-- change is not known until run-time.
-- 
-- /Since: 2.12/
listStoreSet ::
    (B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
    a
    -- ^ /@listStore@/: A t'GI.Gtk.Objects.ListStore.ListStore'
    -> Gtk.TreeIter.TreeIter
    -- ^ /@iter@/: A valid t'GI.Gtk.Structs.TreeIter.TreeIter' for the row being modified
    -> [Int32]
    -- ^ /@columns@/: an array of column numbers
    -> [GValue]
    -- ^ /@values@/: an array of GValues
    -> m ()
listStoreSet :: a -> TreeIter -> [Int32] -> [GValue] -> m ()
listStoreSet listStore :: a
listStore iter :: TreeIter
iter columns :: [Int32]
columns values :: [GValue]
values = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    let nValues :: Int32
nValues = Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ [GValue] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [GValue]
values
    let columns_expected_length_ :: Int32
columns_expected_length_ = Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ [Int32] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int32]
columns
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int32
columns_expected_length_ Int32 -> Int32 -> Bool
forall a. Eq a => a -> a -> Bool
/= Int32
nValues) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
        [Char] -> IO ()
forall a. HasCallStack => [Char] -> a
error "Gtk.listStoreSet : length of 'columns' does not agree with that of 'values'."
    Ptr ListStore
listStore' <- a -> IO (Ptr ListStore)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
listStore
    Ptr TreeIter
iter' <- TreeIter -> IO (Ptr TreeIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreeIter
iter
    Ptr Int32
columns' <- [Int32] -> IO (Ptr Int32)
forall a. Storable a => [a] -> IO (Ptr a)
packStorableArray [Int32]
columns
    [Ptr GValue]
values' <- (GValue -> IO (Ptr GValue)) -> [GValue] -> IO [Ptr GValue]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [GValue]
values
    Ptr GValue
values'' <- Int -> [Ptr GValue] -> IO (Ptr GValue)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray 24 [Ptr GValue]
values'
    Ptr ListStore
-> Ptr TreeIter -> Ptr Int32 -> Ptr GValue -> Int32 -> IO ()
gtk_list_store_set_valuesv Ptr ListStore
listStore' Ptr TreeIter
iter' Ptr Int32
columns' Ptr GValue
values'' Int32
nValues
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
listStore
    TreeIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreeIter
iter
    (GValue -> IO ()) -> [GValue] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [GValue]
values
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
columns'
    Ptr GValue -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr GValue
values''
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ListStoreSetMethodInfo
instance (signature ~ (Gtk.TreeIter.TreeIter -> [Int32] -> [GValue] -> m ()), MonadIO m, IsListStore a) => O.MethodInfo ListStoreSetMethodInfo a signature where
    overloadedMethod = listStoreSet

#endif

-- method ListStore::swap
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "store"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ListStore" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GtkListStore." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "a"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreeIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GtkTreeIter." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "b"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TreeIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Another #GtkTreeIter."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_list_store_swap" gtk_list_store_swap :: 
    Ptr ListStore ->                        -- store : TInterface (Name {namespace = "Gtk", name = "ListStore"})
    Ptr Gtk.TreeIter.TreeIter ->            -- a : TInterface (Name {namespace = "Gtk", name = "TreeIter"})
    Ptr Gtk.TreeIter.TreeIter ->            -- b : TInterface (Name {namespace = "Gtk", name = "TreeIter"})
    IO ()

-- | Swaps /@a@/ and /@b@/ in /@store@/. Note that this function only works with
-- unsorted stores.
-- 
-- /Since: 2.2/
listStoreSwap ::
    (B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
    a
    -- ^ /@store@/: A t'GI.Gtk.Objects.ListStore.ListStore'.
    -> Gtk.TreeIter.TreeIter
    -- ^ /@a@/: A t'GI.Gtk.Structs.TreeIter.TreeIter'.
    -> Gtk.TreeIter.TreeIter
    -- ^ /@b@/: Another t'GI.Gtk.Structs.TreeIter.TreeIter'.
    -> m ()
listStoreSwap :: a -> TreeIter -> TreeIter -> m ()
listStoreSwap store :: a
store a :: TreeIter
a b :: TreeIter
b = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr ListStore
store' <- a -> IO (Ptr ListStore)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
store
    Ptr TreeIter
a' <- TreeIter -> IO (Ptr TreeIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreeIter
a
    Ptr TreeIter
b' <- TreeIter -> IO (Ptr TreeIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TreeIter
b
    Ptr ListStore -> Ptr TreeIter -> Ptr TreeIter -> IO ()
gtk_list_store_swap Ptr ListStore
store' Ptr TreeIter
a' Ptr TreeIter
b'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
store
    TreeIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreeIter
a
    TreeIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TreeIter
b
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ListStoreSwapMethodInfo
instance (signature ~ (Gtk.TreeIter.TreeIter -> Gtk.TreeIter.TreeIter -> m ()), MonadIO m, IsListStore a) => O.MethodInfo ListStoreSwapMethodInfo a signature where
    overloadedMethod = listStoreSwap

#endif