{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.ListStore
(
ListStore(..) ,
IsListStore ,
toListStore ,
noListStore ,
#if defined(ENABLE_OVERLOADING)
ResolveListStoreMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ListStoreAppendMethodInfo ,
#endif
listStoreAppend ,
#if defined(ENABLE_OVERLOADING)
ListStoreClearMethodInfo ,
#endif
listStoreClear ,
#if defined(ENABLE_OVERLOADING)
ListStoreInsertMethodInfo ,
#endif
listStoreInsert ,
#if defined(ENABLE_OVERLOADING)
ListStoreInsertAfterMethodInfo ,
#endif
listStoreInsertAfter ,
#if defined(ENABLE_OVERLOADING)
ListStoreInsertBeforeMethodInfo ,
#endif
listStoreInsertBefore ,
#if defined(ENABLE_OVERLOADING)
ListStoreInsertWithValuesvMethodInfo ,
#endif
listStoreInsertWithValuesv ,
#if defined(ENABLE_OVERLOADING)
ListStoreIterIsValidMethodInfo ,
#endif
listStoreIterIsValid ,
#if defined(ENABLE_OVERLOADING)
ListStoreMoveAfterMethodInfo ,
#endif
listStoreMoveAfter ,
#if defined(ENABLE_OVERLOADING)
ListStoreMoveBeforeMethodInfo ,
#endif
listStoreMoveBefore ,
listStoreNew ,
#if defined(ENABLE_OVERLOADING)
ListStorePrependMethodInfo ,
#endif
listStorePrepend ,
#if defined(ENABLE_OVERLOADING)
ListStoreRemoveMethodInfo ,
#endif
listStoreRemove ,
#if defined(ENABLE_OVERLOADING)
ListStoreReorderMethodInfo ,
#endif
listStoreReorder ,
#if defined(ENABLE_OVERLOADING)
ListStoreSetMethodInfo ,
#endif
listStoreSet ,
#if defined(ENABLE_OVERLOADING)
ListStoreSetColumnTypesMethodInfo ,
#endif
listStoreSetColumnTypes ,
#if defined(ENABLE_OVERLOADING)
ListStoreSetValueMethodInfo ,
#endif
listStoreSetValue ,
#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
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
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
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]
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
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
foreign import ccall "gtk_list_store_newv" gtk_list_store_newv ::
Int32 ->
Ptr CGType ->
IO (Ptr ListStore)
listStoreNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
[GType]
-> m 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
foreign import ccall "gtk_list_store_append" gtk_list_store_append ::
Ptr ListStore ->
Ptr Gtk.TreeIter.TreeIter ->
IO ()
listStoreAppend ::
(B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
a
-> 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
foreign import ccall "gtk_list_store_clear" gtk_list_store_clear ::
Ptr ListStore ->
IO ()
listStoreClear ::
(B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
a
-> 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
foreign import ccall "gtk_list_store_insert" gtk_list_store_insert ::
Ptr ListStore ->
Ptr Gtk.TreeIter.TreeIter ->
Int32 ->
IO ()
listStoreInsert ::
(B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
a
-> Int32
-> 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
foreign import ccall "gtk_list_store_insert_after" gtk_list_store_insert_after ::
Ptr ListStore ->
Ptr Gtk.TreeIter.TreeIter ->
Ptr Gtk.TreeIter.TreeIter ->
IO ()
listStoreInsertAfter ::
(B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
a
-> Maybe (Gtk.TreeIter.TreeIter)
-> 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
foreign import ccall "gtk_list_store_insert_before" gtk_list_store_insert_before ::
Ptr ListStore ->
Ptr Gtk.TreeIter.TreeIter ->
Ptr Gtk.TreeIter.TreeIter ->
IO ()
listStoreInsertBefore ::
(B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
a
-> Maybe (Gtk.TreeIter.TreeIter)
-> 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
foreign import ccall "gtk_list_store_insert_with_valuesv" gtk_list_store_insert_with_valuesv ::
Ptr ListStore ->
Ptr Gtk.TreeIter.TreeIter ->
Int32 ->
Ptr Int32 ->
Ptr GValue ->
Int32 ->
IO ()
listStoreInsertWithValuesv ::
(B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
a
-> Int32
-> [Int32]
-> [GValue]
-> 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
foreign import ccall "gtk_list_store_iter_is_valid" gtk_list_store_iter_is_valid ::
Ptr ListStore ->
Ptr Gtk.TreeIter.TreeIter ->
IO CInt
listStoreIterIsValid ::
(B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
a
-> Gtk.TreeIter.TreeIter
-> m Bool
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
foreign import ccall "gtk_list_store_move_after" gtk_list_store_move_after ::
Ptr ListStore ->
Ptr Gtk.TreeIter.TreeIter ->
Ptr Gtk.TreeIter.TreeIter ->
IO ()
listStoreMoveAfter ::
(B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
a
-> Gtk.TreeIter.TreeIter
-> Maybe (Gtk.TreeIter.TreeIter)
-> 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
foreign import ccall "gtk_list_store_move_before" gtk_list_store_move_before ::
Ptr ListStore ->
Ptr Gtk.TreeIter.TreeIter ->
Ptr Gtk.TreeIter.TreeIter ->
IO ()
listStoreMoveBefore ::
(B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
a
-> Gtk.TreeIter.TreeIter
-> Maybe (Gtk.TreeIter.TreeIter)
-> 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
foreign import ccall "gtk_list_store_prepend" gtk_list_store_prepend ::
Ptr ListStore ->
Ptr Gtk.TreeIter.TreeIter ->
IO ()
listStorePrepend ::
(B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
a
-> 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
foreign import ccall "gtk_list_store_remove" gtk_list_store_remove ::
Ptr ListStore ->
Ptr Gtk.TreeIter.TreeIter ->
IO CInt
listStoreRemove ::
(B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
a
-> Gtk.TreeIter.TreeIter
-> m Bool
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
foreign import ccall "gtk_list_store_reorder" gtk_list_store_reorder ::
Ptr ListStore ->
Ptr Int32 ->
IO ()
listStoreReorder ::
(B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
a
-> [Int32]
-> 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
foreign import ccall "gtk_list_store_set_column_types" gtk_list_store_set_column_types ::
Ptr ListStore ->
Int32 ->
Ptr CGType ->
IO ()
listStoreSetColumnTypes ::
(B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
a
-> [GType]
-> 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
foreign import ccall "gtk_list_store_set_value" gtk_list_store_set_value ::
Ptr ListStore ->
Ptr Gtk.TreeIter.TreeIter ->
Int32 ->
Ptr GValue ->
IO ()
listStoreSetValue ::
(B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
a
-> Gtk.TreeIter.TreeIter
-> Int32
-> GValue
-> 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
foreign import ccall "gtk_list_store_set_valuesv" gtk_list_store_set_valuesv ::
Ptr ListStore ->
Ptr Gtk.TreeIter.TreeIter ->
Ptr Int32 ->
Ptr GValue ->
Int32 ->
IO ()
listStoreSet ::
(B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
a
-> Gtk.TreeIter.TreeIter
-> [Int32]
-> [GValue]
-> 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
foreign import ccall "gtk_list_store_swap" gtk_list_store_swap ::
Ptr ListStore ->
Ptr Gtk.TreeIter.TreeIter ->
Ptr Gtk.TreeIter.TreeIter ->
IO ()
listStoreSwap ::
(B.CallStack.HasCallStack, MonadIO m, IsListStore a) =>
a
-> Gtk.TreeIter.TreeIter
-> Gtk.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